Impure elemental subroutines can simulate for loops over collections

In Python and other languages, you can loop over a collection without indexing the elements, for example

for name in ["Backus","Stroustrup","Ierusalimschy"]:
   print("inventor was",name)

I have wanted such functionality in Fortran and see that impure elemental subroutines can simulate this in some cases. If you want to print a table showing the dependence of a function of several variables on each variable, you can write loops, but this can also be done with an impure elemental subroutine. Here is an example using the Black-Scholes option pricing formula. The program

program xblack_scholes
use kind_mod         , only: dp
use black_scholes_mod, only: call_price
implicit none
real(kind=dp), parameter :: scaling(3) = [0.9_dp,1.0_dp,1.1_dp], s = 42.0_dp, k = 40.0_dp, r = 0.1_dp, t = 0.5_dp, vol = 0.2_dp
! Example 15.6 p360 of Options, Futures, and other Derivatives (2015), 9th edition,
! by John C. Hull
write (*,"(*(a8))") "s","k","r","t","vol","price"
write (*,"(60x,'vary s')")
call print_call_price(scaling*s,k,r,t,vol) ! equivalent to the following for loop
! for ss in [scaling*s]
!   call print_call_price(ss,k,r,t,vol)
! end for
write (*,"(60x,'vary k')")
call print_call_price(s,scaling*k,r,t,vol)
write (*,"(60x,'vary r')")
call print_call_price(s,k,scaling*r,t,vol)
write (*,"(60x,'vary t')")
call print_call_price(s,k,r,scaling*t,vol)
write (*,"(60x,'vary vol')")
call print_call_price(s,k,r,t,scaling*vol)
!
contains
impure elemental subroutine print_call_price(s,k,r,t,vol)
! Black-Scholes price of a European call option
real(kind=dp), intent(in) :: s     ! stock price
real(kind=dp), intent(in) :: k     ! strike price
real(kind=dp), intent(in) :: r     ! annual interest rate -- 0.02 means 2%
real(kind=dp), intent(in) :: t     ! time to expiration in years
real(kind=dp), intent(in) :: vol   ! annualized volatility -- 0.30 means 30%
write (*,"(*(f8.4))") s,k,r,t,vol,call_price(s,k,r,t,vol)
end subroutine print_call_price
end program xblack_scholes

with other modules defined here

gives output

       s       k       r       t     vol   price
                                                            vary s
 37.8000 40.0000  0.1000  0.5000  0.2000  2.0156
 42.0000 40.0000  0.1000  0.5000  0.2000  4.7594
 46.2000 40.0000  0.1000  0.5000  0.2000  8.3813
                                                            vary k
 42.0000 36.0000  0.1000  0.5000  0.2000  7.9340
 42.0000 40.0000  0.1000  0.5000  0.2000  4.7594
 42.0000 44.0000  0.1000  0.5000  0.2000  2.4372
                                                            vary r
 42.0000 40.0000  0.0900  0.5000  0.2000  4.6204
 42.0000 40.0000  0.1000  0.5000  0.2000  4.7594
 42.0000 40.0000  0.1100  0.5000  0.2000  4.9000
                                                            vary t
 42.0000 40.0000  0.1000  0.4500  0.2000  4.5286
 42.0000 40.0000  0.1000  0.5000  0.2000  4.7594
 42.0000 40.0000  0.1000  0.5500  0.2000  4.9847
                                                            vary vol
 42.0000 40.0000  0.1000  0.5000  0.1800  4.5878
 42.0000 40.0000  0.1000  0.5000  0.2000  4.7594
 42.0000 40.0000  0.1000  0.5000  0.2200  4.9396
1 Like

Well-designed Generics facility in Fortran would include intrinsic support for user-defined containers and iterators toward them. Then such looping over collections (instances of containers) should become native to the language.

In the mean time though, for the specific example shown, a verbose option in Fortran would be:

   associate ( name => [character(len=13) :: "Backus","Stroustrup","Ierusalimschy"] )
      print "(*('Inventor was ',g0:,/))", name
   end associate
2 Likes