aboutsummaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/deferred_character_5.f90
diff options
context:
space:
mode:
Diffstat (limited to 'gcc/testsuite/gfortran.dg/deferred_character_5.f90')
-rw-r--r--gcc/testsuite/gfortran.dg/deferred_character_5.f9032
1 files changed, 32 insertions, 0 deletions
diff --git a/gcc/testsuite/gfortran.dg/deferred_character_5.f90 b/gcc/testsuite/gfortran.dg/deferred_character_5.f90
new file mode 100644
index 00000000000..b5d64b43840
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/deferred_character_5.f90
@@ -0,0 +1,32 @@
+! { dg-do run }
+!
+! Tests that PR63932 stays fixed.
+!
+! Contributed by Valery Weber <valeryweber@hotmail.com>
+!
+module mod
+ type :: t
+ character(:), allocatable :: c
+ integer :: i
+ contains
+ procedure, pass :: get
+ end type t
+ type :: u
+ character(:), allocatable :: c
+ end type u
+contains
+ subroutine get(this, a)
+ class(t), intent(in) :: this
+ character(:), allocatable, intent(out), optional :: a
+ if (present (a)) a = this%c
+ end subroutine get
+end module mod
+
+program test
+ use mod
+ type(t) :: a
+ type(u) :: b
+ a%c = 'something'
+ call a%get (a = b%c)
+ if (b%c .ne. 'something') call abort
+end program test