summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03')
-rw-r--r--gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f0327
1 files changed, 27 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03 b/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03
new file mode 100644
index 000000000..069a99b34
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/intrinsic_shadow_3.f03
@@ -0,0 +1,27 @@
+! { dg-do compile }
+! { dg-options "-Wno-intrinsic-shadow -fall-intrinsics" }
+
+! PR fortran/33141
+! Check that the "intrinsic shadow" warnings are not emitted if the warning
+! is negated.
+
+MODULE testmod
+ IMPLICIT NONE
+
+CONTAINS
+
+ REAL FUNCTION asin (arg) ! { dg-bogus "shadow the intrinsic" }
+ IMPLICIT NONE
+ REAL :: arg
+ END FUNCTION asin
+
+END MODULE testmod
+
+REAL FUNCTION acos (arg) ! { dg-bogus "of an intrinsic" }
+ IMPLICIT NONE
+ REAL :: arg
+END FUNCTION acos
+
+! We do only compile, so no main program needed.
+
+! { dg-final { cleanup-modules "testmod" } }