I know it might seem confusing, but it actually has to be like that. Because at the time of the pointer association, iall is not allocated, so that association actually does not change the pointer association status, which remains to null(). And this is regardless to what happen to iall right after, because there is no association between the two. So, yes, the pointer is always not associated in this case.
Exactly, in order to effectively change the pointer association status.
For example, consider the opposite situation:
program main
implicit none
integer, target :: ints(4) = [1, 2, 3, 4]
integer, allocatable, target :: iall(:)
integer, pointer :: iptr(:)
allocate(iall(2))
iptr => iall
call checkAlloc(iall)
call checkAlloc(iptr)
deallocate(iall)
call checkAlloc(iptr)
contains
subroutine checkAlloc(var)
integer, optional :: var(..)
if (present(var)) then
print *, ' Var is "allocated"'
return
endif
print *, ' Var is NOT "allocated"'
end subroutine
end program main
Both of three calls will print Var is "allocated". Any change to the associated variable status (whenever possible) does not affect the status the associated pointer.
Just a possible suggestion.
Introduce a generic_case statement (or whatever name you like) like:
module foo
implicit none
generic_case bar
module procedure bar_a
module procedure bar_na
end generic_case
contains
subroutine bar_na(a,b)
integer, intent(in ) :: a(:)
integer, intent( out) :: b(:)
b = -a
end subroutine
subroutine bar_a(a,b)
integer, intent(in ) :: a(:)
integer, intent( out), allocatable :: b(:)
b = -a
end subroutine
end module
where the generic procedure are searched in order for the first match.
Contrary to the interface case you may forbid to add a procedure to the generic case automatically as I will show later.
This solve the problem with additional procedures.
For example in this case if the second array is an allocatable the first procedure will be selected as is the first that match.
While if it where:
generic_case bar
module procedure bar_na
module procedure bar_a
end generic_case
In this case the first procedure will always be selected and the second one will be shadowed.
A compiler may be required to report if a procedure is shadowed.
You may provide a possible way to extend it but one have to be careful especially if more then one module is involved.
One a possibility is to allow the extension only by listing the generic_case names from which the extension is taken, as before in the given order, like.
module a
generic_case proc
...
end generic_case
...
module b
generic_case proc
...
end generic_case
module d
use a, only: proc_a => proc
use b, only: proc_b => proc
generic_case, extends(proc_a, proc_b) :: proc
...
end generic_case
...
And the order in which proc_a and proc_b are declared in generic_case matters.