Run-time check failure in recursive function - recursion

When I compile my program with runtime-checks, I get the following error (and I have no idea why):
ifort -check all test.f90 -o test
./test
forrtl: severe (193): Run-Time Check Failure. The variable 'my_sum$2$_2' is being used without being defined
Image PC Routine Line Source
sum 0000000000403098 Unknown Unknown Unknown
sum 0000000000403098 Unknown Unknown Unknown
sum 0000000000403098 Unknown Unknown Unknown
sum 0000000000403098 Unknown Unknown Unknown
.
.
.
sum 0000000000403098 Unknown Unknown Unknown
sum 0000000000402EAF Unknown Unknown Unknown
sum 0000000000402DE6 Unknown Unknown Unknown
libc.so.6 00007F7FEB268BE5 Unknown Unknown Unknown
sum 0000000000402CD9 Unknown Unknown Unknown
The code is:
program test
implicit none
real(8) :: x
x=my_sum(lambda_i,0,200)
print*,x
contains
function lambda_i(n) result(i)
real(8) :: i
integer,intent(in) :: n
i=dble(n)
end function
recursive function my_sum(f,i,n) result(s)
implicit none
real(8) :: s
integer, intent(in) :: i,n
interface
function f(n)
implicit none
real(8) :: f
integer,intent(in) :: n
end function
end interface
if ( n .ge. 0 ) s=f(n)+my_sum(f,i,n-1)
end function
end program
Anyone an idea? Without the check the program runs fine unless I reach the recursion limit.

I think the problem is
if ( n .ge. 0 ) s=f(n)+my_sum(f,i,n-1)
Once you reach n .lt. 0, the return value s is not defined, and the function returns an undefined variable (just as ifort complains). Since this is the final step in your recursion, and all other results depend on that, the total result is undefined.
This can be avoided by using
if ( n .ge. 0 ) then
s=f(n)+my_sum(f,i,n-1)
else
s=0._8
endif

Related

Fortran pointer to arbitrary elements of an array [duplicate]

I want to define a pointer to a subarray. For a simple range this is easily done by pointer => array(i:j), but I can't figure out how to do this for a map like k=[k1,k2,k3]. If I would define another array I could use a loop like array2=[(array1(k(j)),j=1,size(k,1))]. But it isn't possible to assign a pointer in a similar way (pointer => [(array1(k(j)),j=1,size(k,1))]) since the r.h.s. of the expression seems to define another variabel which then not even has the target attribute. For simple tasks, a trick around this, is to first assign a pointer to the total array an to use the map on the readout. But in my case this doesn't seem to be possible.
I will attach to examples: The first one shows what I described above. The second one is a more complicated example, where the trick doesn't work anymore. And in addition a two dimensional map is required.
Minimal example:
program test
integer, parameter :: n=10,n_k=3
real,target :: a(1:n)
real :: b(1:n_k)
integer :: k(1:n_k)
integer :: j
real,pointer :: p(:)
! fill array a and define map k:
a=[(real(j),j=1,n)]
k=[((j+1)*2,j=1,n_k)]
! can be used to print the arrays:
!write(*,*) a
!write(*,*) k
! can be used to write only the part of a defined by k:
!write(*,*) (a(k(j)),j=1,n_k)
! this an similar things didn't work:
!p(1:n_k) => [(a(k(j)),j=1,n_k)]
! works, but not generally:
p => a
write(*,*) (p(k(j)),j=1,n_k)
! works, only for arrays:
b=(/(a(k(j)),j=1,n_k)/)
write(*,*) b
end program
More complicated (but also kind of minimal) example which shows (hopefully) the problem I really have. For an easy understanding some explanation leads through it. There are plenty of write commands to print the arrays. I appreciate for the amount of code, but I really don't see how to make a shorter and understandable working example:
module mod1
type base
real :: a
end type
type,extends(base) :: type1
end type
type,extends(base) :: type2
type(type1),allocatable :: b(:)
end type
type(type2),allocatable,target :: c(:)
contains
subroutine printer(z)
class(*),pointer,dimension(:) :: z
integer :: j,a_z,n_z
character(len=40) :: f,ff='(F10.2,1x))',form_z
! define format for printing:
a_z=lbound(z,1)
n_z=ubound(z,1)
write(f,'(I0)') (n_z-a_z+1)
form_z="("//trim(adjustl(f))//ff
! writing:
select type(z)
class is (base)
write(*,form_z) (z(j)%a,j=a_z,n_z)
end select
end subroutine
end module
program test
use mod1
integer,parameter :: n_b=8,n_c=6,n_js=3,n_ls=2
integer :: js(1:n_js),ls(1:n_ls)
integer :: j,l
class(*),pointer :: p(:)
character(len=40) :: f,ff='(F10.2,1x))',form_c,form_b
! define format for printing:
write(f,'(I0)') n_b
form_b="("//trim(adjustl(f))//ff
write(f,'(I0)') n_c
form_c="("//trim(adjustl(f))//ff
! creating and filling the arrays:
allocate(c(n_c))
c%a=[(2d0*real(j),j=1,n_c)]
do j=1,n_c
allocate(c(j)%b(n_b))
c(j)%b%a=[(real(l)*1d1**(j-1),l=1,n_b)]
end do
! write arrays to compare later:
write(*,form_c) c%a
write(*,*)
write(*,form_b) (c(j)%b%a,j=1,n_c)
write(*,*)
! denfining two maps (size and entries will be input in the final program):
js=[1,4,6]
ls=[2,7]
! using the maps to print only the desired entries:
write(*,*) (c(js(j))%a,j=1,n_js)
write(*,*)
write(*,*) ((c(js(j))%b(ls(l))%a,j=1,n_js),l=1,n_ls)
write(*,*)
! !!! here I want to use the maps as well, but so far I only know how to use ranges:
p => c(1:4)
call printer(p)
write(*,*)
p => c(2)%b(3:6)
call printer(p)
write(*,*)
end program
Edit:
Just for the record, I solved the problem now by using arrays of derived types including pointers and slightly changing the calling subroutines.
You cannot do this with pointer association (e.g. pointer1 => array1(vector_subscript). Section 7.2.2.2 of the Fortran 2008 standard that disallows this is:
R733 pointer-assignment-stmt is data-pointer-object [ (bounds-spec-list) ] => data-target
There are two other forms, but they do not match your use, nor would they change the outcome. Reading further:
R737 data-target is variable
C724 (R737) A variable shall have either the TARGET or POINTER attribute, and shall not be an array section with a vector subscript.
This is why you cannot perform the pointer association your are attempting. You can however work around this and with pointer allocation. See this code:
n_k = 3
k = [((j+1)*2,j=1,n_k)] ! a vector subscript
p => a(k) ! NOT OK. Violates C724
allocate(p(n_k)) ! Associate your pointer this way
p = a(k) ! This is OK.
write(*,*) p
Which yields (wrapped in your example program):
% ./ptrtest
4.00000000 6.00000000 8.00000000
This allocates p to be the proper size and then assigns from a with a vector subscript. This gets around the issue of directly associating p with a map of a. This snippet assumes the variables are declared and initialized per your example code. This shows that you can assign a vector subscript of an array to a pointer, but only one that is already associated, not during the association.
As noted in a comment to your Q, if you have a regular stride, you can make the pointer association directly. For your first test case, this would be equivalent and work:
p => a(4:2:8) ! Allocation to a strided array is allowed
If however, you have an irregular vector subscript then the method in this answer will be what you need to use to accomplish the pointer association.
Another workaround you can use is passing a pointer and the map to a procedure. Consider the following code:
program test
implicit none
integer, parameter :: nx = 10, nx_m = 3
integer,dimension(nx_m) :: x_map
integer :: i
real, dimension(nx),target :: a
real, dimension(:), pointer :: p
! initialize array
a = [(real(i*2),i=1,10)]
write (*,'(10(f5.1 x))') a
!define a map
x_map = [1, 9, 4]
! associate pointer
p => a
call print_map(p, x_map)
contains
subroutine print_map(apointer, map)
implicit none
real, dimension(:), pointer :: apointer
integer, dimension(:) :: map
write (*,*) apointer(map)
end subroutine print_map
end program test
In this case, p "knows" about a and the map of elements in a can be calculated in the caller. Rather than associating (=>) p as a map of a (which cannot be done), p is associated to a and the map passed along with it.
This code produces the output:
% ./ptrtest3
2.0 4.0 6.0 8.0 10.0 12.0 14.0 16.0 18.0 20.0
2.00000000 18.0000000 8.00000000

Overflow error when using large size pointer array in Intel fortran

how can I avoid getting an overflow error when using a big size pointer array
My code is simply creating a subroutine to read a file and get data and store it in two arrays (the dimension of the array is to be declared inside the function)
the dimension of the two arrays is declared inside the subroutine, and to allocate them and get them out of the subroutine without the pointer, it gives the error
ARRAY1 is a dummy argument and so cannot be ALLOCATABLE
Here is the code and the error is in the line of the subroutine call
! declaration Main code
CHARACTER*200 :: configfile = "config.txt"
INTEGER*4, DIMENSION(:,:), ALLOCATABLE :: add_array(:,:), route_array(:,:)
call ReadConfigfile(configfile, array1, array2)
and the subroutine is
SUBROUTINE ReadConfigfile(fname, array1, array2)
integer :: dim1, dim2
CHARACTER*200 :: fname
INTEGER*4, POINTER :: array1(:,:), array2(:,:)
some statements to get the dimension from the file
allocate(array2(dim1,5), array2(dim2,5))
some statements to get store the numbers from the file into array1 & array2
END SUBROUTINE ReadConfigfile
and the error I get is
Integer overflow at address 004019933 in file flowaccumulation.95 at line 161

Odd behavior of fortran strings in a derived type after accessing the type by a pointer

[Working example at the end of this post!]
I'm trying to write a simple module to handle physical units in arithmetic operations. My aim is to create derived units out of primary ones.
As you can see in the following code, I have a derived type, namely unit_t, which stores a string, representing the unit itself, power of the unit, conversion factor (to convert it to SI), a logical variable to show if the unit is cloned and next and prev pointers which point to the next or previous unit (in case we have a combination of units, for example kg * m / s**2, so basically it's a linked list connecting different units to each other).
I have a function named unit_clone to clone a primary unit. The unit_int_pow function overloads the exponentiation operator (**) and it simply clones a given primary unit and updates its exponent. The units_mul function overloads the multiplication operator (*). This function first check if the two given units are cloned (if not, it clones them) and then just connect them using next and prev pointers.
Here is my code (you should be able to compile it with gfortran)
module units
implicit none
type unit_t
character(len=16) :: symb
integer :: pow
real :: conv
logical :: cloned
type(unit_t), pointer :: next => null(), prev => null()
end type unit_t
! definitions
type(unit_t), target :: m = unit_t("m", 1, 1.d0, .false.)
type(unit_t), target :: km = unit_t("km", 1, 1.d3, .false.)
type(unit_t), target :: kg = unit_t("kg", 1, 1.d0, .false.)
type(unit_t), target :: s = unit_t("s", 1, 1.d0, .false.)
interface operator (**)
procedure unit_int_pow
end interface operator (**)
interface operator (*)
procedure units_mul
end interface operator (*)
contains
!> Cloning a given node (unit)
function unit_clone(u) result (clone)
implicit none
type(unit_t), intent(in) :: u
type(unit_t), allocatable, target :: clone
allocate(clone)
clone%symb = u%symb
clone%conv = u%conv
clone%pow = u%pow
clone%cloned = .true.
clone%next => u%next
clone%prev => u%prev
end function unit_clone
!> integer powers
function unit_int_pow(u1, p) result(u)
implicit none
type(unit_t), intent(in) :: u1
integer, intent(in) :: p
type(unit_t), allocatable, target :: u
u = unit_clone(u1)
u%pow = u%pow * p
end function unit_int_pow
!> multiplication
function units_mul (u1, u2) result (u1c)
implicit none
type(unit_t), intent(in) :: u1, u2
type(unit_t), allocatable, target :: u1c, u2c
if ( u1%cloned ) then
u1c = u1
else
u1c = unit_clone(u1)
end if
if ( u2%cloned ) then
u2c = u2
else
u2c = unit_clone(u2)
end if
u2c%prev => u1c
u1c%next => u2c
end function units_mul
end module units
program test
use units
implicit none
type(unit_t) :: u
u = kg**2 * m
print *, u%symb, "^", u%pow, " [expected: kg^2]"
print *, u%next%symb, "^", u%next%pow, " [expected: m^1]"
print *, u%next%prev%symb, "^", u%next%prev%pow, " [expected: kg^2]"
end program test
The problem is, I'm getting the following output:
kg ^ 2 [expected: kg^2]
�ȷ2�U ^ 1 [expected: m^1]
�ȷ2�U ^ 2 [expected: kg^2]
Apparently, after accessing the next or next%prev unit (which is basically the head of this short linked list), the code outputs random character instead of the symbs. If I change the order of the variables in the derived type, unit_t, for example if I put symb at the end of the derived type, I will get right symbs, but this time wrong pows.
Any idea what is the culprit of this rather odd behavior?
Using Rudrigo's comment below, I rewrote the code, and it works fine now. Just for the reference, the working code is as follows (if you have further suggestion or modification, please let me know, Nombre respository)
module units
implicit none
type unit_t
character(len=16) :: symb
real :: conv
real :: pow = 1.d0
logical :: cloned = .false.
type(unit_t), pointer :: next => null(), prev => null()
end type unit_t
! units definitions
type(unit_t), target :: m = unit_t("m", 1.d0)
type(unit_t), target :: km = unit_t("km", 1.d3)
type(unit_t), target :: kg = unit_t("kg", 1.d0)
type(unit_t), target :: s = unit_t("s", 1.d0)
interface operator (**)
procedure unit_int_pow
end interface operator (**)
interface operator (*)
procedure units_mul
end interface operator (*)
contains
!> Cloning a given node (unit)
function unit_clone(u) result (clone)
implicit none
type(unit_t), intent(in) :: u
type(unit_t), pointer :: clone
allocate(clone)
clone%symb = trim(u%symb)
clone%conv = u%conv
clone%pow = u%pow
clone%cloned = .true.
clone%next => u%next
clone%prev => u%prev
end function unit_clone
!> integer powers
function unit_int_pow(u1, p) result(u)
implicit none
type(unit_t), intent(in) :: u1
integer, intent(in) :: p
type(unit_t), pointer :: u
if ( u1%cloned ) then
! TODO: should be able to handle complex cases like: a * (b * c)**3
! most likly, only updating the power of the linked list chain
! would do the job
else
u => unit_clone(u1)
end if
u%pow = u%pow * p
end function unit_int_pow
!> multiplication
function units_mul (u1, u2) result (u2c)
implicit none
type(unit_t), intent(in), target :: u1, u2
type(unit_t), pointer :: u2c
if ( u2%cloned ) then
if ( associated(u2%prev) ) then
u2c => u2%prev%next
else
u2c => u2
end if
else
u2c => unit_clone(u2)
end if
if ( u1%cloned ) then
if ( associated(u2%prev) ) then
u2c%prev => u1%prev%next
else
u2c%prev => u1
end if
else
u2c%prev => unit_clone(u1)
end if
u2c%prev%next => u2c
end function units_mul
end module units
A pointer in Fortran has three posible association status:
associated: the pointer is actually pointing to a defined and allocated variable / matching data storage (its target);
disassociated: it was (or is part of an objects that was) explicitly nullified or deallocated, or its target was properly disassociated.
undefined: anything different than the former, e.g. its target is (or became) undefined, or was deallocated by other means than by calling deallocate directly in the pointer itself, among other causes.
When execution of an instance of a subprogram completes (e.g. when function units_mul reaches end function), any unsaved local variable becomes undefined. Also, any allocatable local variable that is not saved or is a function result gets deallocated, and when an allocatable entity is deallocated, it also becomes undefined.
Back to your problem, u2c is an allocatable unsaved local variable inside units_mul function, where you associate u1c%next to it. When this function reaches the end, u2c ends its lifecycle and becomes undefined, bringing u1c%next to become also undefined, in a state referred in the Fortran lingo as dangling pointer.
This a text from the Fortran Standard describing this phenomena (even though it is referring to the case of modules host association, it's the same logic):
Note 19.10
A pointer from a module program unit might be accessible in a
subprogram via use association. Such pointers have a lifetime that is
greater than targets that are declared in the subprogram, unless such
targets are saved. Therefore, if such a pointer is associated with a
local target, there is the possibility that when a procedure defined
by the subprogram completes execution, the target will cease to exist,
leaving the pointer “dangling”. This document considers such pointers
to have an undefined association status. They are neither associated
nor disassociated. They cannot be used again in the program until
their status has been reestablished. A processor is not required to
detect when a pointer target ceases to exist.
A dangling pointer is not a reliable pointer, and the compiler has no control over it. They may, by any reason, keep pointing to their last memory address (and accidentally give the expected result in some cases, or the values would be gibberish from random memory address), but it will most certainly break, and the fail can be anything, from just wrong results to a SIGSEG fault or a memory address violation.
See this example code:
program dangling_pointer
implicit none
integer, pointer :: p(:)
integer, allocatable :: a(:)
call sub1(p)
print *, 'sub1: ', p
call sub2(p)
print *, 'sub2: ', p
call sub3(p, a)
print *, 'sub3: ', p
p => fun4()
print *, 'fun4: ', p
contains
subroutine sub1(dummy_p)
! the pointer passed as argument outlives the local target
! when the procedure ends, it becomes a "dangling pointer"
integer, pointer :: dummy_p(:)
integer, allocatable, target :: local_a(:)
allocate(local_a(5))
local_a = 100
dummy_p => local_a
end
subroutine sub2(dummy_p)
! here the local variable is saved, so it persists. No problem here.
integer, pointer :: dummy_p(:)
integer, allocatable, target, save :: saved_a(:)
allocate(saved_a(5))
saved_a = 100
dummy_p => saved_a
end
subroutine sub3(dummy_p, out_a)
! here the target is a passed argument, so it persists. No problem here.
integer, pointer :: dummy_p(:)
integer, allocatable, target :: out_a(:)
allocate(out_a(5))
out_a = 100
dummy_p => out_a
end
function fun4() result(result_p)
! here the function result will be returned as a pointer. No problem here.
integer, pointer :: result_p(:)
allocate(result_p(5))
result_p = 100
end
end
With gfortran 9.0.0 I get:
sub1: 14316208 0 14287184 0 100
sub2: 100 100 100 100 100
sub3: 100 100 100 100 100
fun4: 100 100 100 100 100
Edit
I think this snippet would work for your problem:
allocate(u1c%next)
if (u2%cloned) then
u1c%next = u2
else
u1c%next = unit_clone(u2)
end if
u1c%next%prev => u1c

Passing a null pointer actual argument to a member procedure of a derived type

Is passing a null pointer to a function and a subroutine valid according
to the Fortran 2003 standard? Please suppose that the called function and
the subroutine can correctly handle the case in which the dummy argument is
a null pointer. I am especially interested in the case where such function and
subroutine are a 'member' function and subroutine of a derived type.
I would like to avoid checking the association status of each pointer in the
calling side if it is allowed by standard, in much the same way that I don't
have to treat the zero-size array separately. At the same time, I do not want to
rely on a behavior not specified by the standard.
As far as I tried with the following example, ifort and gfortran showed
different behaviors regarding this point.
moo.f90
MODULE moo
IMPLICIT NONE
PRIVATE
PUBLIC LL
TYPE LL
INTEGER :: i0
CONTAINS
PROCEDURE :: func1
PROCEDURE :: func2
END type LL
CONTAINS
FUNCTION func1(self) RESULT(pLL_dest)
TYPE(LL), POINTER :: pLL_dest
CLASS(LL), TARGET, INTENT(IN) :: self
write(*,*) 'hello from func1'
pLL_dest => null()
!pLL_dest => self
END FUNCTION func1
FUNCTION func2(self) RESULT(flg)
LOGICAL :: flg
CLASS(LL), TARGET, INTENT(IN) :: self
write(*,*) 'hello from func2'
flg = .true.
END FUNCTION func2
END MODULE moo
main.f90
PROGRAM chk_nullpo
USE moo, ONLY : LL
IMPLICIT NONE
!CLASS(LL), POINTER :: pLL_s=>null()
TYPE(LL), POINTER :: pLL_s=>null()
TYPE(LL), POINTER :: pLL_d=>null()
LOGICAL :: flg
write(*,*) 'associated(pLL_s) =',associated(pLL_s)
write(*,*) 'associated(pLL_d) =',associated(pLL_d)
write(*,*) 'func1..'
pLL_d => pLL_s%func1()
write(*,*) 'associated(pLL_s) =',associated(pLL_s)
write(*,*) 'associated(pLL_d) =',associated(pLL_d)
write(*,*) 'func2..'
flg =pLL_s%func2()
write(*,*) 'flg=', flg
write(*,*) 'associated(pLL_s) =',associated(pLL_s)
write(*,*) 'associated(pLL_d) =',associated(pLL_d)
write(*,*) 'normal end'
END PROGRAM chk_nullpo
Executable generated by ifort caused a run-time error when the member
subroutine func2 is called with the null pointer.
$ ifort -v
ifort version 14.0.2
$ ifort -c moo.f90 -stand f03 -warn all -check
$ ifort -c main.f90 -stand f03 -warn all -check
$ ifort -o ex_ifort moo.o main.o -stand f03 -warn all -check
ifort: warning #10182: disabling optimization; runtime debug checks enabled
$ ./ex_ifort
associated(pLL_s) = F
associated(pLL_d) = F
func1..
hello from func1
associated(pLL_s) = F
associated(pLL_d) = F
func2..
forrtl: severe (408): fort: (7): Attempt to use pointer PLL_S when it is not associated with a target
Image PC Routine Line Source
ex_ifort 0000000000402AE1 Unknown Unknown Unknown
ex_ifort 0000000000402336 Unknown Unknown Unknown
libc.so.6 00002AC53B23DF45 Unknown Unknown Unknown
ex_ifort 0000000000402229 Unknown Unknown Unknown
$
On the other hand, executable generated by gfortran finished without error.
$ gfortran --version
GNU Fortran (Ubuntu 4.8.4-2ubuntu1~14.04.3) 4.8.4
Copyright (C) 2013 Free Software Foundation, Inc.
GNU Fortran comes with NO WARRANTY, to the extent permitted by law.
You may redistribute copies of GNU Fortran
under the terms of the GNU General Public License.
For more information about these matters, see the file named COPYING
$ gfortran -c moo.f90 -std=f2003 -Wall -fbounds-check
moo.f90:26.21:
FUNCTION func2(self) RESULT(flg)
1
Warning: Unused dummy argument 'self' at (1)
moo.f90:16.21:
FUNCTION func1(self) RESULT(pLL_dest)
1
Warning: Unused dummy argument 'self' at (1)
$ gfortran -c main.f90 -std=f2003 -Wall -fbounds-check
$ gfortran -o ex_gfortran moo.o main.o -std=f2003 -Wall -fbounds-check
$ ./ex_gfortran
associated(pLL_s) = F
associated(pLL_d) = F
func1..
hello from func1
associated(pLL_s) = F
associated(pLL_d) = F
func2..
hello from func2
flg= T
associated(pLL_s) = F
associated(pLL_d) = F
normal end
$
Is the behavior of ifort not comforming the standard, or
is the behavior of gfortran just graceful? Or, the standard doesn't
say anything about this point?
I note that both of these compilers are older versions, and I guess
a newer version might show different behavior.
Both compilers are behaving in a legitimate way here. That is, the code is faulty but not in a way which requires a compiler to provide diagnostics.
Look at the pointer assignment statement
pLL_d => pLL_s%func1()
This is a reference to the binding name func1 of type LL. However, at the point execution reaches here pLL_s is not associated. The procedure reference is therefore not allowed. According to Fortran 2008 12.5.1:
The data-ref in a procedure-designator shall not be ... a pointer that is not associated.
As this is not a numbered constraint it is the responsibility of the programmer to ensure compliance.
Moving on beyond this problem to the general question "is passing a null pointer to a function and a subroutine valid?", the answer is "yes, as long as its use doesn't violate the usual conditions".
In summary, although conceptually the reference in
pLL_d => pLL_s%func1() ! Using func1 as a binding name
is like that in
pLL_d => func1(pLL_s) ! For the module's procedure func1
the problem isn't that pLL_s is a not associated pointer actual argument. That latter form is allowed but the former isn't.1
Of interest for this question is the requirement about definition of the function result. For func1 the function result is a pointer, so it is necessary that the association status of the result be defined. If the function is referenced by its binding name then necessarily the association status of self is defined. Indeed, self is associated.
1 That's actually a little of an oversimplification. While it's true that a procedure may be allowed an actual argument that is a not associated pointer, that doesn't hold for those procedures here.
Look at the declaration of the dummy arguments
CLASS(LL), TARGET, INTENT(IN) :: self
Here self is a non-optional non-pointer dummy. To be argument associated with a pointer actual argument that actual argument must be pointer associated. So, the functions aren't ones which "correctly handle the case in which the dummy argument is a null pointer".
That said, there'd be nothing wrong with a statement like
pLL_d => pLL_s%func1(ptr) ! or
pLL_d => func1(pLL_s, ptr)
with pLL_s pointer associated and ptr a potentially non-associated actual corresponding to a pointer dummy. The passed-object dummy argument is really just a very special case.

Fortran array pointers to scalar

In Fortran, you can reshape arrays with pointers:
program working
implicit none
integer, dimension(:,:), pointer :: ptr
integer, dimension(6), target :: trg
trg = (/1,2,3,4,5,6/)
ptr(1:2,1:3) => trg
! Here, you can use the 6-sized 1D array trg
! or the 2 by 3-sized 2D array ptr at the same time.
! Both have the same content (6 integers), but are only indexed
! differently.
write(*,*) ptr(1,2)
end program working
This program writes "3", which is according to the reshape rules.
Similarly, I attempted to do the same, but not with 1D to 2D, but 0D to 1D.
program not_working
implicit none
integer, dimension(:), pointer :: ptr
integer, target :: trg
trg = 1
ptr(1:1) => trg
! I hoped to be able to use the scalar trg at the same time as
! the one-sized 1D array ptr. I thought they both have the same
! content, but are only indexed differently.
write(*,*) ptr(1)
end program not_working
I expected to see a "1". But it does not compile.
Gfortran 4.9 says:
Error: Rank remapping target must be rank 1 or simply contiguous at
(1)
Ifort 14.0.2 says:
<file>.f90: catastrophic error: Internal compiler error:
segmentation violation signal raised Please report this error along
with the circumstances in which it occurred in a Software Problem
Report. Note: File and line given may not be explicit cause of this
error. compilation aborted for <file>.f90 (code 1)
I do not understand how the scalar trg can be not contiguous and what the fundamental difference between the two example programs is.
The scalar is not simply contiguous array because it is not an array at all. It is as simple as that. Gfortran detects it and complains, ifort is confused and crashes. But your code is invalid, you cannot point an array pointer on a scalar.
Array pointers are desinged to point to arrays, so cannot point to scalars (instead, we can use scalar pointers for this purpose). But if we definitely want to use array pointers to point to scalars (for some reason), we could use c_f_pointer() such that
use iso_c_binding
integer, target :: a
integer, pointer :: p(:), q(:,:), r(:,:,:)
a = 777
call c_f_pointer( c_loc( a ), p, [1] )
call c_f_pointer( c_loc( a ), q, [1,1] )
call c_f_pointer( c_loc( a ), r, [1,1,1] )
print *, "p = ", p(:), "with shape", shape(p)
print *, "q = ", q(:,:), "with shape", shape(q)
print *, "r = ", r(:,:,:), "with shape", shape(r)
But this is clearly an "unsafe" feature (in the sense that it allows access to raw memory), and if used with wrong arguments, it could give a wrong result (or even disaster), for example:
call c_f_pointer( c_loc( a ), p, [3] )
print *, "p = ", p(:) !! gives "p = 777 202 0" etc with garbage data
So, unless there is some special reason, I think it is probably better (safer) to use scalar pointers for scalar variables...

Resources