Hi all,
recently read this in the gfortran manual
GNU Fortran passes most arguments by reference, i.e. by passing a pointer to the data. Note that the compiler might use a temporary variable into which the actual argument has been copied, if required semantically (copy-in/copy-out).
Consider this module :
module addition
use,intrinsic :: iso_fortran_env,only: real64
implicit none
private
public :: add_two_numbers,add_two_numbers_using_pointers
contains
pure function add_two_numbers(number1,number2) result(sum_of_two)
real(kind=real64),intent(in) :: number1,number2
real(kind=real64) :: sum_of_two
sum_of_two = number1 + number2
end function add_two_numbers
pure function add_two_numbers_using_pointers(number1,number2) result(sum_of_two)
real(kind=real64),pointer,intent(in) :: number1,number2
real(kind=real64) :: sum_of_two
sum_of_two = number1 + number2
end function add_two_numbers_using_pointers
end module addition
and these two main programs
main without pointers :
program main
use,intrinsic :: iso_fortran_env,only: real64
use addition
implicit none
real(kind=real64) :: data1,data2
write(unit=*,fmt="(a,1x)",advance="no") "Please enter two numbers:"
read *, data1,data2
print "(a,1x,f12.6)", "The sum is:",add_two_numbers(data1, data2)
end program main
main with pointers :
program main
use,intrinsic :: iso_fortran_env,only: real64
use addition
implicit none
real(kind=real64),target :: data1,data2
write(unit=*,fmt="(a,1x)",advance="no") "Please enter two numbers:"
read *, data1,data2
print "(a,1x,f12.6)", "The sum is:",add_two_numbers_using_pointers(data1, data2)
end program main
- When I use
valgrind
on both the programs, they appear to use the same amount of memory. Why is that ? - In which instances are variables fully copied and not just referenced ?
- When are pointers useful in Fortran ?