2 ! PR46990 - class array implementation
4 ! Contributed by Wolfgang Kilian on comp.lang.fortran - see comment #7 of PR
13 generic :: assignment(=) => assign ! define generic assignment
16 type, extends(base_type) :: extended_type
18 end type extended_type
22 impure elemental subroutine assign (a, b)
23 class(base_type), intent(out) :: a
24 type(base_type), intent(in) :: b
28 subroutine reallocate (a)
29 class(base_type), dimension(:), allocatable, intent(inout) :: a
30 class(base_type), dimension(:), allocatable :: tmp
31 allocate (tmp (2 * size (a))) ! how to alloc b with same type as a ?
32 if (trim (print_type ("tmp", tmp)) .ne. "tmp is base_type") call abort
33 tmp(:size(a)) = a ! polymorphic l.h.s.
34 call move_alloc (from=tmp, to=a)
35 end subroutine reallocate
37 character(20) function print_type (name, a)
38 character(*), intent(in) :: name
39 class(base_type), dimension(:), intent(in) :: a
41 type is (base_type); print_type = NAME // " is base_type"
42 type is (extended_type); print_type = NAME // " is extended_type"
51 class(base_type), dimension(:), allocatable :: a
53 allocate (extended_type :: a(10))
54 if (trim (print_type ("a", a)) .ne. "a is extended_type") call abort
56 if (trim (print_type ("a", a)) .ne. "a is base_type") call abort