Reputation: 29
I tried to write a code in modern fortran (2018?) and one of my goals is to be able to convert subroutines like this one (old fortran 77) to the most recent fortran (2018?)
subroutine nobin(e,j,f)
common/binin/bini(40),nbn
er=e
do 100 i=j,40
er=er-bini(i)
if(er.le.0.0) go to 200
100 continue
f1=er/bini(40)
f=41.+f1-float(j)
if(j.gt.40) f=f1
go to 300
200 f=float(i-j)+er/bini(i)+1.0
300 continue
return
end
So far, I was able to write something like this (see below) but I was successful only for scalar variables. I am kind of stuck when I have to use arrays. In particular I should allocate and then give some values to the array Bini (the common block in the old fortran subroutine). And then to use these array in the function (find_bin_nobin) defined in the class. Any suggestion is appreciated as well as any formal improvement to the code. Many Thanks!
module precision
implicit none
public
integer, parameter :: pr = selected_real_kind(12,300)
integer, parameter :: ir = 4
end module precision
module constants
use precision
implicit none
public
real ( kind = pr ), parameter :: zero = 0.0_pr
real ( kind = pr ), parameter :: one = 1.0_pr
real ( kind = pr ), parameter :: four = 4.0_pr
real ( kind = pr ), parameter :: pi = four * atan(one)
end module constants
module class_Dntrnpr
use precision
use constants, only : zero, one
implicit none
type Find_bin
real ( kind = pr ) :: e
integer( kind = ir ) :: j
real ( kind = pr ), allocatable, dimension(:) :: bin
contains
procedure :: f => find_bin_nobin
end type Find_bin
contains
function find_bin_nobin(x, n) result(f)
class(Find_bin), intent(inout) :: x
integer( kind = ir ), intent(in) :: n
real ( kind = pr ) :: f, f1, er
integer( kind = ir ) :: i, k
allocate(x%bin(n))
er = x%e
i = x%j
k = i
er = er - x%bin(i)
do while ( er <= zero )
er = er - x%bin(i)
i = i + 1
enddo
f1 = er / x%bin(n)
f = ( n + 1 ) + f1 - dble(k)
if ( k > n ) then
f = f1; return
else
f = dble(i-k) + er / x%bin(i) + one
endif
return
end function find_bin_nobin
end module class_Dntrnpr
program test
use class_Dntrnpr
implicit none
integer( kind = ir ) :: nbmax,i
real ( kind = pr ), allocatable, dimension(:) :: bini
type(Find_bin) :: en
! type(Find_bin), allocatable, dimension(:) :: bin
en%e = 2.0
en%j = 1
nbmax = 40
allocate(bini(nbmax))
bini = 1.0
end program test
Upvotes: 2
Views: 333
Reputation: 2981
This looks like it might be more suited to code review, but I'm going to throw in my six cents anyway. Apologies in advance if I come off rude below; it's not my intent, I'm just trying to make suggestions as I see them, and to avoid cluttering advice with niceties.
module precision
implicit none
public
integer, parameter :: pr = selected_real_kind(12,300)
integer, parameter :: ir = 4
end module precision
selected_real_kind(15,307)
is more standard than (12,300)
for double precision. Maybe consider instead using real64
from iso_fortran_env
.selected_int_kind(9)
is more portable than 4
.So I would write this as:
module precision
implicit none
public
integer, parameter :: pr = selected_real_kind(15,307)
integer, parameter :: ir = selected_int_kind(9)
end module precision
module constants
use precision
implicit none
public
real ( kind = pr ), parameter :: zero = 0.0_pr
real ( kind = pr ), parameter :: one = 1.0_pr
real ( kind = pr ), parameter :: four = 4.0_pr
real ( kind = pr ), parameter :: pi = four * atan(one)
end module constants
zero = 0.0_pr
are generally bad practice. With a modern compiler they won't give you any speedup, and they reduce readability. Just use the actual numbers.real(pr)
over real (kind = pr)
. It conveys the same information, and is more concise.So I would write this as:
module constants
use precision
implicit none
public
real(pr), parameter :: pi = 4.0_pr * atan(1.0_pr)
end module constants
module class_Dntrnpr
use precision
use constants, only : zero, one
implicit none
type Find_bin
real ( kind = pr ) :: e
integer( kind = ir ) :: j
real ( kind = pr ), allocatable, dimension(:) :: bin
contains
procedure :: f => find_bin_nobin
end type Find_bin
contains
e
and j
).Find_bin
to something more descriptive. Is this class a "find bin"?bin
represent a single bin, or should it be bins
?f => find_bin_nobin
should really be nobin => nobin_Find_bin
.find_bin_nobin
does two different things: intilalise bin
and calculate f
. Ideally, OOP procedures should be separated into subroutine
s which modify their arguments and function
s which do not modify their arguments. In this case, initialising bin
can be done in a constructor.So I would write this as:
module class_Find_bin
use precision
implicit none
type Find_bin
real(pr) :: e
integer(ir) :: j
real(pr), allocatable, dimension(:) :: bin
contains
procedure :: nobin => nobin_Find_bin
end type Find_bin
! Constructor for type Find_bin.
interface Find_bin
module procedure new_Find_bin
end interface
contains
contains
function find_bin_nobin(x, n) result(f)
class(Find_bin), intent(inout) :: x
integer( kind = ir ), intent(in) :: n
real ( kind = pr ) :: f, f1, er
integer( kind = ir ) :: i, k
allocate(x%bin(n))
er = x%e
i = x%j
k = i
er = er - x%bin(i)
do while ( er <= zero )
er = er - x%bin(i)
i = i + 1
enddo
f1 = er / x%bin(n)
f = ( n + 1 ) + f1 - dble(k)
if ( k > n ) then
f = f1; return
else
f = dble(i-k) + er / x%bin(i) + one
endif
return
end function find_bin_nobin
end module class_Dntrnpr
find_bin_nobin
into a constructor and a function to calculate f
.x%bin
. You allocate it with allocate(x%bin(n))
, but then start reading from it without setting its values first.i
is different to the old version.k
is unnecessary and adds confusion.dble(foo)
should be real(foo, pr)
.;
for two lines in one.if(j.gt.40)
doesn't have an else
. The line 200 f=float(i-j)+er/bini(i)+1.0
is always skipped by the line go to 300
.return
at the end of a procedure. That happens automatically.So I would write this as:
contains
function new_Find_bin(e, j, n) result(this)
real(pr), intent(in) :: e
integer(ir), intent(in) :: j
integer(ir), intent(in) :: n
type(Find_bin) :: this
this%e = e
this%j = j
allocate(this%bin(n))
! Initialise bin here.
end function
function nobin_Find_bin(this) result(f)
class(Find_bin), intent(in) :: this
real(pr) :: f
real(pr) :: f1, er
integer(ir) :: i, n
er = this%e
n = size(this%bin)
do i=this%j,n
er = er - this%bin(i)
if (er<=0.0_pr) then
f = real(i-this%j, pr) + er/this%bin(i) + 1.0_pr
return
endif
enddo
f1 = er / this%bin(n)
f = ( n + 1 ) + f1 - real(this%j, pr)
if ( this%j > n ) then
f = f1
endif
end function find_bin_nobin
end module class_Find_bin
program test
use class_Dntrnpr
implicit none
integer( kind = ir ) :: nbmax,i
real ( kind = pr ), allocatable, dimension(:) :: bini
type(Find_bin) :: en
! type(Find_bin), allocatable, dimension(:) :: bin
en%e = 2.0
en%j = 1
nbmax = 40
allocate(bini(nbmax))
bini = 1.0
end program test
With the modules changed as above, I would write this as:
program test
use class_Find_bin
implicit none
type(Find_bin) :: bin
real(pr) :: f
bin = Find_bin(2.0_pr, 1, 40)
f = bin%nobin()
end program
e
and er
with error
if that's what they represent.Upvotes: 2