summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/common_errors_1.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/common_errors_1.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/common_errors_1.f9038
1 files changed, 38 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/common_errors_1.f90 b/gcc/testsuite/gfortran.dg/common_errors_1.f90
new file mode 100644
index 000000000..0d4e1beb3
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/common_errors_1.f90
@@ -0,0 +1,38 @@
+! { dg-do compile }
+! Tests a number of error messages relating to derived type objects
+! in common blocks. Originally due to PR 33198
+
+subroutine one
+type a
+ sequence
+ integer :: i = 1
+end type a
+type(a) :: t ! { dg-error "Derived type variable .t. in COMMON at ... may not have default initializer" }
+common /c/ t
+end
+
+subroutine first
+type a
+ integer :: i
+ integer :: j
+end type a
+type(a) :: t ! { dg-error "Derived type variable .t. in COMMON at ... has neither the SEQUENCE nor the BIND.C. attribute" }
+common /c/ t
+end
+
+subroutine prime
+type a
+ sequence
+ integer, allocatable :: i(:)
+ integer :: j
+end type a
+type(a) :: t ! { dg-error "Derived type variable .t. in COMMON at ... has an ultimate component that is allocatable" }
+common /c/ t
+end
+
+subroutine source
+parameter(x=0.) ! { dg-error "COMMON block .x. at ... is used as PARAMETER at ..." }
+common /x/ i ! { dg-error "COMMON block .x. at ... is used as PARAMETER at ..." }
+intrinsic sin
+common /sin/ j ! { dg-error "COMMON block .sin. at ... is also an intrinsic procedure" }
+end subroutine source