summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/public_private_module_8.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/public_private_module_8.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/public_private_module_8.f9049
1 files changed, 49 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/public_private_module_8.f90 b/gcc/testsuite/gfortran.dg/public_private_module_8.f90
new file mode 100644
index 0000000000..bfc1b368f4
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/public_private_module_8.f90
@@ -0,0 +1,49 @@
+! { dg-do compile }
+! { dg-options "-O2" }
+!
+! PR fortran/54884
+!
+! Check that get_key_len is not optimized away as it
+! is used in a publicly visible specification expression.
+!
+
+module m
+ private
+ public :: foo
+ interface foo
+ module procedure bar
+ end interface foo
+contains
+ pure function mylen()
+ integer :: mylen
+ mylen = 42
+ end function mylen
+ pure function myotherlen()
+ integer :: myotherlen
+ myotherlen = 99
+ end function myotherlen
+ subroutine bar(x)
+ character(len=mylen()) :: x
+ character :: z2(myotherlen())
+ call internal(x)
+ block
+ character(len=myotherlen()) :: z
+ z = "abc"
+ x(1:5) = z
+ end block
+ x(6:10) = intern_func()
+ contains
+ function intern_func()
+ character(len=myotherlen()) :: intern_func
+ intern_func = "zuzu"
+ end function intern_func
+ subroutine internal(y)
+ character(len=myotherlen()) :: y
+ y = "abc"
+ end subroutine internal
+ end subroutine bar
+end module m
+
+! { dg-final { scan-assembler-not "__m_MOD_myotherlen" } }
+! { dg-final { scan-assembler "__m_MOD_bar" } }
+! { dg-final { scan-assembler "__m_MOD_mylen" } }