Well, if one wanted to simply show the strength and diversity of modern Fortran, especially in terms of Fortran being an evolving multiparadigm language with focus on numerical computing and performance, a silly illustrator can also be as follows, it’s not as short as you seek but not all that long either:
module m
type :: numseq_t(n)
integer, len :: n = 3
integer :: vals(n)
contains
procedure, pass(this) :: calc => calc_seq
end type
contains
elemental subroutine calc_seq( this )
class(numseq_t(n=*)), intent(inout) :: this
integer :: i, lb, ub
lb = (this_image()-1)*size(this%vals) ; ub = lb + size(this%vals) - 1
this%vals = fibonacci_number( [( i, i = lb, ub )] )
end subroutine
elemental integer function fibonacci_number( n ) result(num)
integer, intent(in) :: n
select case ( n )
case ( 0:1 )
num = n
case default
num = fibonacci_number(n-1) + fibonacci_number(n-2)
end select
end function
end module
use m, only : numseq_t
type(numseq_t(n=5)) :: numseq[*]
integer :: i
call numseq%calc()
sync all
if ( this_image() == 1 ) then
do i = 1, num_images()
write( *, fmt="(*(g0,1x))", advance="no" ) numseq[i]%vals
end do
end if
end
You will notice the example builds on recent newbie discussions on this forum with
- recursion to determine a number sequence, the Fibonacci series here,
- the use of structured programming in program flow,
- modular programming with auto-generated explicit interfaces to procedures,
- the use of explicit INTENTs with procedure parameters,
- along with functional programming aspects to process arrays elementally,
- it combines that with object-oriented design to establish a “store” of number sequences,
- it hints at templated programming via a parameterized type for the store, and
- it employs parallel programming toward the calculations to stock that store of sequences
So you can see there is a lot going on in there that touches upon many of the facilities now available in Fortran.
Here’s the expected output using one processor that outputs the first 40 elements (5 per parallel compute image times 8 images) in the Fibonacci sequence:
C:\Temp>ifort /standard-semantics /Qcoarray:shared /Qcoarray-num-images=8 e.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.-out:e.exe
-subsystem:console
e.objC:\Temp>e.exe
0 1 1 2 3 5 8 13 21 34 55 89 144 233 377 610 987 1597 2584 4181 6765 10946 17711 28657 46368 75025 121393 196418 317811 514229 832040 1346269 2178309 3524578 5702887 9227465 14930352 24157817 39088169 63245986