diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 80f78c12a6d62981a2919788bac511805d6e4a3b..0db8ce51016bcc829320971c48fe3fda6bdaf3b6 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,9 @@
+2010-06-02  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/44360
+	* parse.c (gfc_fixup_sibling_symbols): Do not "fix" use-associated
+	symbols.
+
 2010-06-01  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
 
 	PR fortran/44371
diff --git a/gcc/fortran/parse.c b/gcc/fortran/parse.c
index 31ad7cf385ce7decc41fc32ec8965b98484913a4..7fc35418bec41345a9516b949548f1b790b8c833 100644
--- a/gcc/fortran/parse.c
+++ b/gcc/fortran/parse.c
@@ -3667,6 +3667,7 @@ gfc_fixup_sibling_symbols (gfc_symbol *sym, gfc_namespace *siblings)
 		  || (old_sym->ts.type != BT_UNKNOWN
 			&& !old_sym->attr.implicit_type)
 		  || old_sym->attr.flavor == FL_PARAMETER
+		  || old_sym->attr.use_assoc
 		  || old_sym->attr.in_common
 		  || old_sym->attr.in_equivalence
 		  || old_sym->attr.data
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index cbda12be222921efbba82b4122cae7904791c554..c15d70839c538a56e8982ff0c520456c048cd4d6 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,8 @@
+2010-06-02  Tobias Burnus  <burnus@net-b.de>
+
+	PR fortran/44360
+	* gfortran.dg/use_13.f90: New test case.
+
 2010-06-01  Jerry DeLisle  <jvdelisle@gcc.gnu.org>
 
 	PR fortran/44371
diff --git a/gcc/testsuite/gfortran.dg/use_13.f90 b/gcc/testsuite/gfortran.dg/use_13.f90
new file mode 100644
index 0000000000000000000000000000000000000000..1fe7b1eacf2d361f4af67a63aa85fa5b400c6a2b
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/use_13.f90
@@ -0,0 +1,45 @@
+! { dg-do run }
+!
+! PR fortran/44360
+!
+! Test-case based on a contribution of Vittorio Zecca.
+!
+! The used subroutine was not the use-associated but the host associated one!
+! The use-associated function/variable were already working properly.
+!
+module m
+  integer :: var = 43
+contains
+ integer function fun()
+   fun = 42
+ end function fun
+ subroutine fun2()
+   var = 44
+ end subroutine fun2
+end module m
+
+module m2
+  integer :: var = -2
+contains
+ subroutine test()
+   ! All procedures/variables below refer to the ones in module "m"
+   ! and not to the siblings in this module "m2".
+   use m 
+   if (fun() /= 42) call abort()
+   if (var /= 43) call abort()
+   call fun2()
+   if (var /= 44) call abort()
+ end subroutine test
+ integer function fun()
+   call abort()
+   fun = -3
+ end function fun
+ subroutine fun2()
+   call abort()
+ end subroutine fun2
+end module m2
+
+use m2
+call test()
+end
+! { dg-final { cleanup-modules "m m2" } }