4 ! Contributed by Juergen Reuter <juergen.reuter@desy.de>
16 type(t1_t), dimension(:), allocatable :: p
18 procedure :: func => t2_func
22 type(t2_t), public :: int_born
29 function t2_func (int) result (p)
30 class(t2_t), intent(in) :: int
31 type(t1_t), dimension(:), allocatable :: p
35 subroutine evaluate (t3)
36 class(t3_t), intent(inout) :: t3
37 type(t1_t), dimension(:), allocatable :: p_born
38 allocate (p_born(1:size(t3%int_born%func ())), &
39 source = t3%int_born%func ())
40 if (.not. allocated(p_born)) call abort()
41 if (size(p_born) /= 5) call abort()
42 end subroutine evaluate