fortran-courses/Intermediate Fortran/Section 2 - Procedure Attri.../abstract_type_reduce.f90

58 lines
1.2 KiB
Fortran

module reduce_m
implicit none
type, abstract :: accumulator_t
contains
procedure(combiner), deferred, nopass :: combine
end type
abstract interface
pure function combiner(x, y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
end function
end interface
contains
pure recursive function reduce(vals, accumulator, init) result(combined)
integer, intent(in) :: vals(:)
class(accumulator_t), intent(in) :: accumulator
integer, intent(in) :: init
integer :: combined
if (size(vals) == 1) then
combined = accumulator%combine(init, vals(1))
else
combined = reduce(vals(2:), accumulator, accumulator%combine(init, vals(1)))
end if
end function
end module
module multiplier_m
use reduce_m, only: accumulator_t
implicit none
type, extends(accumulator_t) :: multiplier_t
contains
procedure, nopass :: combine => multiply
end type
contains
pure function multiply(x, y) result(z)
integer, intent(in) :: x
integer, intent(in) :: y
integer :: z
z = x * y
end function
end module
program main
use multiplier_m, only: multiplier_t
use reduce_m, only: reduce
implicit none
print *, reduce([1, 2, 3, 4], multiplier_t(), 1)
end program