Surely ChatGPT is not optimized for the task, it refuses to operate on external data, so the only way to input a piece of code for modernize is copy-and-paste. Also, it still makes some errors in that, but is willing to learn, although one would have to check if the wisdom learnt is permanent. What follows is an interesting dialogue with ChatGPT (it is sort of TL;DR post, so only for those interested )
Me: modernize following old Fortran code; remove goto wherever possible, change loops over arrays into array expressions, add interfaces to subprograms:
(following ‘original’ code was, after some trial-and-error, copy-pasted in the input form. ChatGPT, when responded, cited it fully, with the format changed to free and ::
added in declarations - my code was in fixed format and w/o ::
)
Original Code
! Original Fortran code
program main
integer :: i, j, n, m
real :: a(100, 100), b(100), c(100)
data c /100*-1.0/
n = 100
m = 100
do 5 i=1,100
do 4 j=1,100
a(i,j) = 2.2
4 continue
5 continue
10 continue
do i = 1, n
b(i) = 0
do j = 1, m
b(i) = b(i) + a(i, j)
end do
end do
do i = 1, n
c(i) = b(i)
end do
if (c(n) .lt. 0) then
goto 10
end if
end program
Modernized code
! Modernized Fortran code
program main
integer, parameter :: n = 100, m = 100
integer :: i
real, dimension(n) :: a(m, n), b, c
a = 2.2
c = -1.0
do while (c(n) < 0)
b = sum(a, dim = 2)
c = b
end do
end program
Me: very good, now please extract the ‘do while’ loop into separate subroutine to be called with arrays a, b and c as arguments. Add interface to that subroutine, provide intent attributes to dummy arguments
ChatGPT:
Modernized Code, v.2
! Modernized Fortran code
program main
use calculate_sum
implicit none
integer, parameter :: n = 100, m = 100
integer :: i
real, dimension(n) :: a(m, n), b, c
a = 2.2
c = -1.0
call calculate_sum(a, b, c)
end program
subroutine calculate_sum(a, b, c)
use, intrinsic :: iso_fortran_env
implicit none
real, dimension(:,:), intent(in) :: a
real, dimension(:), intent(out) :: b
real, dimension(:), intent(inout) :: c
integer :: i
do while (c(size(c)) < 0)
b = sum(a, dim = 2)
c = b
end do
end subroutine
In the modernized code, we extracted the do while
loop into a separate subroutine called calculate_sum
. We added an interface to the subroutine, which specifies the type and dimensions of the arguments that are passed to the subroutine. We also added intent attributes to the dummy arguments of the subroutine, which indicates whether the argument is an input, output, or inout argument. This allows the compiler to check the compatibility of the arguments when calling the subroutine and ensures that the subroutine can be called from other programs.
We also added the use
statement to the main
program and the calculate_sum
subroutine, which allows them to access the calculate_sum
subroutine. We also added the implicit none
statement, which disables the default implicit typing rules and requires that all variables be explicitly declared. This can help to avoid errors and improve the readability of the code. Additionally, we used the iso_fortran_env
intrinsic module to get the size of the c
array in the do while
loop, instead of using a hardcoded value. This makes the code more portable and easier to maintain.
Me: you have used ‘use calculate_sum’ statement to access the subroutine but this is an error. ‘use’ statement can be used exclusively to access modules and module subprograms. The subroutine calculate_sum
as you wrote it is an external subroutine, not a module. So you have either to enclose it in a module or get rid of the use
statement and add a interface block
ChatGPT: You are correct, the use of the use
statement to access the calculate_sum
subroutine is not correct. As you pointed out, the use
statement can only be used to access modules and module subprograms, not external subroutines.
Here is a possible modernization of the old Fortran code that uses an interface block to specify the type and dimensions of the arguments that are passed to the calculate_sum
subroutine:
"Modernized Code v.3
! Modernized Fortran code
program main
implicit none
integer, parameter :: n = 100, m = 100
integer :: i
real, dimension(n) :: a(m, n), b, c
a = 2.2
c = -1.0
call calculate_sum(a, b, c)
end program
subroutine calculate_sum(a, b, c)
use, intrinsic :: iso_fortran_env
implicit none
real, dimension(:,:) :: a
real, dimension(:) :: b
real, dimension(:) :: c
integer :: i
do while (c(size(c)) < 0)
b = sum(a, dim = 2)
c = b
end do
end subroutine
interface
subroutine calculate_sum(a, b, c)
real, dimension(:,:) :: a
real, dimension(:) :: b
real, dimension(:) :: c
end subroutine
end interface
In the modernized code, we removed the use
statement and added an interface block to specify the type and dimensions of the arguments that are passed to the calculate_sum
subroutine. This allows the compiler to check the compatibility of the arguments when calling the subroutine and ensures that the subroutine can be called from other programs.
We also added the implicit none
statement to the main
program and the calculate_sum
subroutine, which disables the default implicit typing rules and requires that all variables be explicitly declared. This can help to avoid errors and improve the readability of the code. Additionally, we used the iso_fortran_env
intrinsic module to get the size of the c
array in the do while
loop, instead of using a hardcoded value. This makes the code more portable and easier to maintain.
Me: much better but still needs some correction. The interface block cannot be placed outside any program unit. It must be included inside that unit which is going to access the subprogram being interfaced. Also, using the intrinsic functions as size()
does not require iso_fortran_env
module. Please do not include the original code any more, only the modernized version
ChatGPT: (the output code was interrupted and still contained interface block outside, I do not quote it here)
Me: well, you did not correct the placement of the interface block. It must be located inside the main program
ChatGPT: You are correct, the placement of the interface block in the previous modernization of the code is incorrect. The interface block must be placed inside the program unit that is going to access the subprogram being interfaced.
Here is a possible modernization of the old Fortran code that corrects the placement of the interface block:
"Modernized Code v. 4
! Modernized Fortran code
program main
implicit none
integer, parameter :: n = 100, m = 100
integer :: i
real, dimension(n) :: a(m, n), b, c
a = 2.2
c = -1.0
call calculate_sum(a, b, c)
contains
subroutine calculate_sum(a, b, c)
implicit none
real, dimension(:,:) :: a
real, dimension(:) :: b
real, dimension(:) :: c
integer :: i
do while (c(size(c)) < 0)
b = sum(a, dim = 2)
c = b
end do
end subroutine
end program
interface
subroutine calculate_sum(a, b, c)
real, dimension(:,:) :: a
real, dimension(:) :: b
real, dimension(:) :: c
end subroutine
end interface
In the modernized code, we placed the calculate_sum
subroutine inside the main
program and added a contains
statement to indicate that the (broken text)
Me: You have change the structure of the code by making calculate_sum
an internal subroutine. That is ok, but then no explicit interface block is needed at all. in any case, the interface block cannot be outside program units. In the meantime, you have forgotten to include intent
attributes for dummy arguments of the subroutine
ChatGPT: You are correct, the use of an interface block is not necessary when the subroutine is defined as an internal subroutine. In that case, the type and dimensions of the arguments are inferred from their declarations in the subroutine itself.
Here is a possible modernization of the old Fortran code that removes the unnecessary interface block and adds intent attributes to the dummy arguments of the calculate_sum
subroutine:
"Modernized Code v. 5
! Modernized Fortran code
program main
implicit none
integer, parameter :: n = 100, m = 100
integer :: i
real, dimension(n) :: a(m, n), b, c
a = 2.2
c = -1.0
call calculate_sum(a, b, c)
contains
subroutine calculate_sum(a, b, c)
use, intrinsic :: iso_fortran_env
implicit none
real, dimension(:,:), intent(in) :: a
real, dimension(:), intent(out) :: b
real, dimension(:), intent(inout) :: c
integer :: i
do while (c(size(c)) < 0)
b = sum(a, dim = 2)
c = b
end do
end subroutine
end program
In the modernized code, we removed the unnecessary interface block and added intent attributes to the dummy arguments of the calculate_sum
subroutine. This allows the compiler to check the compatibility (possibly broken text)
To summarize, the potential to use AI to modernize old code is quite impressive. It will be interesting to check if what it learns during human interaction is indeed memorized - probably requires someone else to give ChatGPT similar exercise to do.
The feeling, however, of having a conversation with a living creature, is immense!