aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/use_rename_6.f90
diff options
context:
space:
mode:
authorH.J. Lu <hongjiu.lu@intel.com>2010-07-23 19:37:40 +0000
committerH.J. Lu <hongjiu.lu@intel.com>2010-07-23 19:37:40 +0000
commite59b0ef2e7a1fb44791d473ee416aeb01fcb169c (patch)
tree437dca120093cc7b1f6debf6f6b31779526c7192 /gcc/testsuite/gfortran.dg/use_rename_6.f90
parentf25b023a0d9de6a6c1e1965d93ba6028cb03fc7d (diff)
parent92ac755201aad4366eaff2b75b3239637bee3590 (diff)
Merged with trunk at revision 162480.ifunc
git-svn-id: https://gcc.gnu.org/svn/gcc/branches/ifunc@162483 138bc75d-0d04-0410-961f-82ee72b054a4
Diffstat (limited to 'gcc/testsuite/gfortran.dg/use_rename_6.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/use_rename_6.f9040
1 files changed, 40 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/use_rename_6.f90 b/gcc/testsuite/gfortran.dg/use_rename_6.f90
new file mode 100644
index 00000000000..02f25c36e97
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/use_rename_6.f90
@@ -0,0 +1,40 @@
+! { dg-do compile }
+! { dg-options "-fdump-tree-original" }
+!
+! PR fortran/44702
+!
+! Based on a test case by Joe Krahn.
+!
+! Multiple import of the same symbol was failing for
+! intrinsic modules.
+!
+subroutine one()
+ use iso_c_binding, only: a => c_ptr, b => c_ptr, c_ptr
+ implicit none
+ type(a) :: x
+ type(b) :: y
+ type(c_ptr) :: z
+end subroutine one
+
+subroutine two()
+ use iso_c_binding, a => c_ptr, b => c_ptr
+ implicit none
+ type(a) :: x
+ type(b) :: y
+end subroutine two
+
+subroutine three()
+ use iso_fortran_env, only: a => error_unit, b => error_unit, error_unit
+ implicit none
+ if(a /= b) call shall_not_be_there()
+ if(a /= error_unit) call shall_not_be_there()
+end subroutine three
+
+subroutine four()
+ use iso_fortran_env, a => error_unit, b => error_unit
+ implicit none
+ if(a /= b) call shall_not_be_there()
+end subroutine four
+
+! { dg-final { scan-tree-dump-times "shall_not_be_there" 0 "original" } }
+! { dg-final { cleanup-tree-dump "original" } }