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

47 lines
925 B
Fortran

module reduce_m
implicit none
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(:)
procedure(combiner) :: accumulator
integer, intent(in) :: init
integer :: combined
if (size(vals) == 1) then
combined = accumulator(init, vals(1))
else
combined = reduce(vals(2:), accumulator, accumulator(init, vals(1)))
end if
end function
end module
module multiplier_m
implicit none
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: multiply
use reduce_m, only: reduce
implicit none
print *, reduce([1, 2, 3, 4], multiply, 1)
end program