Memory leak in Fortran linked list using pointers - pointers

I'm trying to create a linked list structure in Fortran for a fixed point iteration between particles in a computational zone. Particles are iteratively traced through a computational zone, their properties from each step are stored; and they interact with the particle properties from the previous iteration.
For this problem I have two linked lists, one which holds the particle properties from the previous iteration (list_use, with which the particles currently being traced through the domain interact) and another list which accumulates the properties of the particles as they are traced through the computational zone. After one iteration (i.e. after all particles have been traced through the domain once), I want to discard list_use (interactions with this data have already been computed), copy list_buildup into list_use and then discard list_buildup, so that it can be repopulated with the next data from the iteration.
I appear to have a memory leak when copying and discarding the lists. Here's a reduced bit of code which replicates the memory leak. As far as I can tell, the leak occurs in updateASR. I would expect the process memory before this subroutine to be equal to the memory after it, but using the diagnostics on VisualStudio, it shows the memory increasing every time that updateASR is called, eventually leading to the program terminating (with an access violation error). Here's an image showing the VS process memory diagnostic. I guess that destroyASREntries is somehow not doing what I actually want it to do?
I'm not very experienced with pointers in Fortran and therefore a bit stuck, so any help would be really appreciated!
module linked_list
!---------------------------------------------------------------------------------
! Type containing the data for an ASR entry, used to compute interactions between rays.
type ASR_entry
real :: intensity !<- The intensity of the ASR entry
real :: ang_freq !<- Angular frequency
real,dimension(3) :: wavevector !<- Wavevector (x,y,z): Cartesian.
end type ASR_entry
!---------------------------------------------------------------------------------
! A node type in the linked list for the ASR.
type ASR_Node
type(ASR_Node),pointer :: next => null()
type(ASR_Node),pointer :: prev => null()
type(ASR_entry) :: node_entry
end type ASR_Node
!---------------------------------------------------------------------------------
! For interaction, each cell contains one of these ASR linked lists, which itself contains the nodes, which contain the entry.
type ASR_cell_ll
type(ASR_Node),pointer :: head => null() !<- first%next points to first node
type(ASR_Node),pointer :: last => null() !<- last%prev points to last node
integer(kind=4) :: size = 0 !<- Number of ASR entries in the linked list
end type ASR_cell_ll
contains
!---------------------------------------------------------------------------------
! Create the ASR linked list in every cell.
subroutine createASRcell(list)
implicit none
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
!- Allocate memory - is this necessary??
allocate(list)
allocate(list%head,list%last)
list%head%next => list%last !<- If list is empty, then the first entry points to the last entry which is null
list%last%prev => list%head
list%size = 0
end subroutine createASRcell
!---------------------------------------------------------------------------------
! Delete all ASR entries
subroutine destroyASREntries(list)
implicit none
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent=>null(), dNext=>null()
if (.not. associated(list)) return
allocate(dCurrent,dNext)
dCurrent => list%head
dNext => dCurrent%next
!- Deallocate all data nodes in list
do
nullify(dCurrent%prev) !- Remove dangling pointers from the list structure.
deallocate(dCurrent)
if (.not. associated(dNext)) exit
dCurrent => dNext
dNext => dCurrent%next
end do
nullify(dCurrent,dNext) !- Remove dangling pointers
list%size=0
deallocate(list)
end subroutine destroyASREntries
!---------------------------------------------------------------------------------
!- This subroutine removes the old entries in list_use, copies the list_buildup entries into list_use, then empties list_buildip for the next iteration.
subroutine updateASR(list_use, list_buildup)
implicit none
type(ASR_cell_ll),pointer :: list_use, list_buildup
!First destroy all entries from the previous ASR iteration, before recreating the list.
call destroyASREntries(list_use)
call createASRcell(list_use)
!Then make the use list the previous iterations buildup list.
list_use => list_buildup
!The stop buildup from pointing to the use list's new entries, before recreating buildup as blank.
nullify(list_buildup)
call createASRcell(list_buildup)
end subroutine updateASR
end module linked_list
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module definitions
implicit none
integer :: nx,ny,nz,nbeams !Dimensions of the linked list domain.
integer :: ix,iy,iz,ibeam !Loop variables
end module definitions
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program main
use definitions
use linked_list
implicit none
type(asr_cell_ll),pointer :: list_use,list_buildup !<-The temporary and used linked list.
integer :: i
call createASRcell(list_buildup)
call createASRcell(list_use)
do i=1,1000000000
call updateASR(list_use,list_buildup)
enddo
end program main
I compiled the above with ifort.

First, let's look at createASRcell. It returns a ASR_cell_ll with size=0. So why are you allocating memory? You should only allocate a node when you want a node. I think createASRcell should be
subroutine createASRcell(list)
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
list%head => null()
list%last => null()
list%size = 0
end subroutine
Second, let's look at destroyASREntries. The lines
allocate(dCurrent,dNext)
dCurrent => list%head
dNext => dCurrent%next
are creating two nodes, at dCurrent and dNext, and then immediately losing track of these nodes to point dCurrent and dNext at new targets. This will leak the memory you just allocated. The allocate statement just shouldn't be there. There's also quite a lot of excess deallocation going on. Simplifying the subroutine, we get
subroutine destroyASREntries(list)
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent, dNext
if (.not. associated(list)) return
dCurrent => list%head
!- Deallocate all data nodes in list
do while(associated(dCurrent))
dNext => dCurrent%next
nullify(dCurrent%prev)
nullify(dCurrent%next)
deallocate(dCurrent)
dCurrent => dNext
end do
! - Deallocate the list itself
deallocate(list)
end subroutine destroyASREntries
Finally, let's look at updateASR. I don't quite understand what you're trying to do here, but the subroutine is going to cause problems. The lines
call destroyASREntries(list_use)
call createASRcell(list_use)
list_use => list_buildup
will clean up the old ASR_cell_ll pointed to by list_use, create a new empty ASR_cell_ll, again pointed to by list_use, and then immediately lose track of this new list by pointing list_use at list_buildup. This will leak all the memory of the newly created ASR_cell_ll.

Thanks to #veryreverie for their answer which helped solve the leak and clear up my misunderstanding. The issue was due to allocating pointers before then repointing them to new memory in createASRcell and destroyASREntries. Here is the diagnotic with the new code showing no memory leak. Here is the modified, working code without memory leaks in case anyone is interested:
module linked_list
!---------------------------------------------------------------------------------
! Type containing the data for an ASR entry, used to compute interactions between rays.
type ASR_entry
real :: intensity !<- The intensity of the ASR entry
real :: ang_freq !<- Angular frequency
real,dimension(3) :: wavevector !<- Wavevector (x,y,z): Cartesian.
end type ASR_entry
!---------------------------------------------------------------------------------
! A node type in the linked list for the ASR.
type ASR_Node
type(ASR_Node),pointer :: next => null()
type(ASR_Node),pointer :: prev => null()
type(ASR_entry) :: node_entry
end type ASR_Node
!---------------------------------------------------------------------------------
! For interaction, each cell contains one of these ASR linked lists, which itself contains the nodes, which contain the entry.
type ASR_cell_ll
type(ASR_Node),pointer :: head => null() !<- first%next points to first node
type(ASR_Node),pointer :: last => null() !<- last%prev points to last node
integer(kind=4) :: size = 0 !<- Number of ASR entries in the linked list
end type ASR_cell_ll
contains
!---------------------------------------------------------------------------------
! Create the ASR linked list in every cell.
subroutine createASRcell(list)
implicit none
type(ASR_cell_ll), pointer :: list
if(associated(list)) call Abort("Must pass null pointer of type 'ASR_cell_ll' to createASRcell.")
allocate(list)
allocate(list%head,list%last)
list%head%next => list%last !<- If list is empty, then the first entry points to the last entry which is null
list%last%prev => list%head
list%size = 0
end subroutine createASRcell
!---------------------------------------------------------------------------------
! Delete all ASR entries
subroutine destroyASREntries(list)
implicit none
type(ASR_cell_ll), pointer :: list
type(ASR_Node), pointer :: dCurrent=>null(), dNext=>null()
if (.not. associated(list)) return
dCurrent => list%head
!- Deallocate all data nodes in list
do while(associated(dCurrent))
dNext => dCurrent%next
nullify(dCurrent%prev) !- Remove dangling pointers from the list structure.
nullify(dCurrent%next) !- Remove dangling pointers from the list structure.
deallocate(dCurrent)
dCurrent => dNext
end do
! - Deallocate the list itself
deallocate(list)
end subroutine destroyASREntries
!---------------------------------------------------------------------------------
!- This subroutine removes the old entries in list_use, copies the list_buildup entries into list_use, then empties list_buildip for the next iteration.
subroutine updateASR(list_use, list_buildup)
implicit none
type(ASR_cell_ll),pointer :: list_use, list_buildup
call destroyASREntries(list_use) !First destroy all entries from the previous ASR iteration
list_use => list_buildup !Then make the use list the previous iterations buildup list.
nullify(list_buildup) !The stop buildup from pointing to the use list's new entries
end subroutine updateASR
end module linked_list
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
module definitions
implicit none
integer :: nx,ny,nz,nbeams !Dimensions of the linked list domain.
integer :: ix,iy,iz,ibeam !Loop variables
end module definitions
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
program main
use definitions
use linked_list
implicit none
type(asr_cell_ll),pointer :: list_use=>null(),list_buildup=>null() !<-The temporary and used linked list.
integer :: i
call createASRcell(list_buildup)
call createASRcell(list_use)
do i=1,1000000000
call updateASR(list_use,list_buildup)
enddo
end program main

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

Pointers to arrays as member variables in Fortran derived type

In Fortran, it is not possible to make a member variable of a derived type a target. (I guess this has to do with the standard not specifying how a derived type is stored in memory?) However, I can have a pointer as a member variable and associate pointers with pointers. Like I do in the example below.
module DataMod
type DataType
real(8), private, dimension(:,:), pointer, contiguous :: A
real(8), private, dimension(:,:), pointer, contiguous :: B
integer :: n
contains
procedure :: alloc
procedure :: set
procedure :: print_
final :: dealloc
end type DataType
interface DataType
procedure :: NewDataType
end interface DataType
contains
function NewDataType(dimension_) result(new)
integer, intent(in) :: dimension_
type(DataType) :: new
new%n = dimension_
end function NewDataType
subroutine alloc(dataObject)
class(DataType) :: dataObject
allocate(dataObject%A(dataObject%n,dataObject%n))
allocate(dataObject%B(dataObject%n,dataObject%n))
end subroutine alloc
subroutine set(dataObject, datas, choice)
class(DataType) :: dataObject
real(8), dimension(dataObject%n,dataObject%n), intent(in) :: datas
character(len=1), intent(in) :: choice
real(8), dimension(:,:), pointer :: dataPointer
integer :: i,j
if(choice .eq. 'A') then
datapointer => dataObject%A
elseif(choice .eq. 'B') then
datapointer => dataObject%B
else
stop
endif
do j = 1,dataObject%n
do i = 1,dataObject%n
datapointer(i,j) = datas(i,j)
enddo
enddo
end subroutine set
subroutine print_(dataObject)
class(DataType), intent(in) :: dataObject
print *, 'A'
print *, dataObject%A(1:dataObject%n,1:dataObject%n)
print *
print *, 'B'
print *, dataObject%B(1:dataObject%n,1:dataObject%n)
end subroutine print_
subroutine dealloc(dataObject)
type(DataType) :: dataObject
deallocate(dataObject%A)
deallocate(dataObject%B)
end subroutine dealloc
end module DataMod
program DataTest
use DataMod, only: DataType
implicit none
real(8), dimension(2,2) :: testArray
type(DataType) :: testType
testType = DataType(2)
call testType%alloc()
testArray(1,1) = 1
testArray(2,1) = 2
testArray(1,2) = 3
testArray(2,2) = 4
call testType%set(testArray, 'A')
testArray(1,1) = 5
testArray(2,1) = 6
testArray(1,2) = 7
testArray(2,2) = 8
call testType%set(testArray, 'B')
call testType%print_()
end program DataTest
In the set routine, I use an if statement to set a pointer to decide if it should dump the incoming matrix in A or B. In the program I'm currently working on, I must decide which combination of four different matrices to multiply together and setting a pair of pointers is much nicer than writing 16 almost identical calls to dgemm.
My question is if there are any problems with this approach besides the normal dangers of dangling pointers etc. or a way to do this without pointers? The arrays should not be accessed from outside the object. Are there any performance issues?
Components in a type definition may not be declared with the TARGET attribute (beyond the missing syntax, that would be inconsistent with other concepts and rules in the current language), but if a variable of derived type has the TARGET attribute, then all of its subobjects have the TARGET attribute too. For a type definition:
type DataType
real(8), private, dimension(:,:), allocatable :: A
real(8), private, dimension(:,:), allocatable :: B
...
The procedure set could be written...
subroutine set(dataObject, datas, choice)
class(DataType), TARGET :: dataObject
real(8), dimension(dataObject%n,dataObject%n), intent(in) :: datas
character(len=1), intent(in) :: choice
real(8), dimension(:,:), pointer :: dataPointer
! require dataobject%A and ..%B to already be allocated.
if(choice .eq. 'A') then
datapointer => dataObject%A
elseif(choice .eq. 'B') then
datapointer => dataObject%B
else
stop
endif
datapointer = datas ! or some other operation.
...
(dataPointer could be declared contiguous, the allocatable arrays that it gets pointed at are always contiguous.)
An actual argument without the TARGET attribute may be associated with a dummy argument with the TARGET attribute. If this is the case, then pointers associated with the dummy argument become undefined when execution of the procedure completes. (Such pointers may also become undefined in some cases, even when the actual argument has the TARGET attribute - see F2018 15.5.2.4p8 on for details - but these cases don't apply to scalars.)
Consequently, in the general case, if a pointer to one of the components of an object of derived type needs to outlive a procedure like set above (e.g. if dataPointer was not local to set) and you can't ensure that the actual argument will always have the TARGET attribute, then the original method using pointer components may be more appropriate. The implementation in the question appears to be ok - though I would suggest making the finalizer IMPURE ELEMENTAL to make things more robust to future changes.

Can I point to variable ranked arrays in Fortran? [duplicate]

There are basically two ways to pass arrays to a subroutine in Fortran 90/95:
PROGRAM ARRAY
INTEGER, ALLOCATABLE :: A(:,:)
INTEGER :: N
ALLOCATE(A(N,N))
CALL ARRAY_EXPLICIT(A,N)
! or
CALL ARRAY_ASSUMED(A)
END PROGRAM ARRAY
SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N,N)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT
SUBROUTINE ARRAY_ASSUMED(A)
INTEGER, ALLOCATABLE :: A(:,:)
N=SIZE(A,1)
! bla bla
END SUBROUTINE ARRAY_ASSUMED
where you need an explicit interface for the second, usually through the use of a module.
From FORTRAN77, I'm used to the first alternative, and I read this is also the most efficient if you pass the whole array.
The nice thing with the explicit shape is that I can also call a subroutine and treat the array as a vector instead of a matrix:
SUBROUTINE ARRAY_EXPLICIT(A,N)
INTEGER :: N
INTEGER :: A(N**2)
! bla bla
END SUBROUTINE ARRAY_EXPLICIT
I wondered if there is a nice way to do that kind of thing using the second, assumed shape interface, without copying it.
See the RESHAPE intrinsic, e.g.
http://gcc.gnu.org/onlinedocs/gfortran/RESHAPE.html
Alternatively, if you want to avoid the copy (in some cases an optimizing compiler might be able to do a reshape without copying, e.g. if the RHS array is not used afterwards, but I wouldn't count on it), as of Fortran 2003 you can assign pointers to targets of different rank, using bounds remapping. E.g. something like
program ptrtest
real, pointer :: a(:)
real, pointer :: b(:,:)
integer :: n = 10
allocate(a(n**2))
a = 42
b (1:n, 1:n) => a
end program ptrtest
I was looking to do the same thing and came across this discussion. None of the solutions suited my purposes, but I found that there is a way to reshape an array without copying the data using iso_c_binding if you are using the fortran 2003 standard which current fortran 90/95 compilers tend to support. I know the discussion is old, but I figured I would add what I came up with for the benefit of others with this question.
The key is to use the function C_LOC to convert an array to an array pointer, and then use C_F_POINTER to convert this back into a fortran array pointer with the desired shape. One challenge with using C_LOC is that C_LOC only works for array that have a directly specified shape. This is because arrays in fortran with an incomplete size specification (i.e., that use a : for some dimension) include an array descriptor along with the array data. C_LOC does not give you the memory location of the array data, but the location of the descriptor. So an allocatable array or a pointer array don't work with C_LOC (unless you want the location of the compiler specific array descriptor data structure). The solution is to create a subroutine or function that receives the array as an array of fixed size (the size really doesn't matter). This causes the array variable in the function (or subroutine) to point to the location of the array data rather than the location of the array descriptor. You then use C_LOC to get a pointer to the array data location and C_F_POINTER to convert this pointer back into an array with the desired shape. The desired shape must be passed into this function to be used with C_F_POINTER. Below is an example:
program arrayresize
implicit none
integer, allocatable :: array1(:)
integer, pointer :: array2(:,:)
! allocate and initialize array1
allocate(array1(6))
array1 = (/1,2,3,4,5,6/)
! This starts out initialized to 2
print *, 'array1(2) = ', array1(2)
! Point array2 to same data as array1. The shape of array2
! is passed in as an array of intergers because C_F_POINTER
! uses and array of intergers as a SIZE parameter.
array2 => getArray(array1, (/2,3/))
! Change the value at array2(2,1) (same as array1(2))
array2(2,1) = 5
! Show that data in array1(2) was modified by changing
! array2(2,1)
print *, 'array(2,1) = array1(2) = ', array1(2)
contains
function getArray(array, shape_) result(aptr)
use iso_c_binding, only: C_LOC, C_F_POINTER
! Pass in the array as an array of fixed size so that there
! is no array descriptor associated with it. This means we
! can get a pointer to the location of the data using C_LOC
integer, target :: array(1)
integer :: shape_(:)
integer, pointer :: aptr(:,:)
! Use C_LOC to get the start location of the array data, and
! use C_F_POINTER to turn this into a fortran pointer (aptr).
! Note that we need to specify the shape of the pointer using an
! integer array.
call C_F_POINTER(C_LOC(array), aptr, shape_)
end function
end program
#janneb has already answered re RESHAPE. RESHAPE is a function -- usually used in an assignment statement so there will be a copy operation. Perhaps it can be done without copying using pointers. Unless the array is huge, it is probably better to use RESHAPE.
I'm skeptical that the explicit shape array is more efficient than the assumed shape, in terms of runtime. My inclination is to use the features of the Fortran >=90 language and use assumed shape declarations ... that way you don't have to bother passing the dimensions.
EDIT:
I tested the sample program of #janneb with ifort 11, gfortran 4.5 and gfortran 4.6. Of these three, it only works in gfortran 4.6. Interestingly, to go the other direction and connect a 1-D array to an existing 2-D array requires another new feature of Fortran 2008, the "contiguous" attribute -- at least according to gfortran 4.6.0 20110318. Without this attribute in the declaration, there is a compile time error.
program test_ptrs
implicit none
integer :: i, j
real, dimension (:,:), pointer, contiguous :: array_twod
real, dimension (:), pointer :: array_oned
allocate ( array_twod (2,2) )
do i=1,2
do j=1,2
array_twod (i,j) = i*j
end do
end do
array_oned (1:4) => array_twod
write (*, *) array_oned
stop
end program test_ptrs
You can use assumed-size arrays, but it can mean multiple layers of wrapper
routines:
program test
implicit none
integer :: test_array(10,2)
test_array(:,1) = (/1, 2, 3, 4, 5, 6, 7, 8, 9, 10/)
test_array(:,2) = (/11, 12, 13, 14, 15, 16, 17, 18, 19, 20/)
write(*,*) "Original array:"
call print_a(test_array)
write(*,*) "Reshaped array:"
call print_reshaped(test_array, size(test_array))
contains
subroutine print_reshaped(a, n)
integer, intent(in) :: a(*)
integer, intent(in) :: n
call print_two_dim(a, 2, n/2)
end subroutine
subroutine print_two_dim(a, n1, n2)
integer, intent(in) :: a(1:n1,1:*)
integer, intent(in) :: n1, n2
call print_a(a(1:n1,1:n2))
end subroutine
subroutine print_a(a)
integer, intent(in) :: a(:,:)
integer :: i
write(*,*) "shape:", shape(a)
do i = 1, size(a(1,:))
write(*,*) a(:,i)
end do
end subroutine
end program test
I am using ifort 14.0.3 and 2D to 1D conversion, I could use an allocatable array for 2D array and a pointer array for 1D:
integer,allocatable,target :: A(:,:)
integer,pointer :: AP(:)
allocate(A(3,N))
AP(1:3*N) => A
As #M.S.B mentioned, in case both A and AP have the pointer attribute, I had to use contiguous attribute for A to guarantee the consistency of the conversion.
Gfortran is a bit paranoid with interfaces. It not only wants to know the type, kind, rank and number of arguments, but also the shape, the target attribute and the intent (although I agree with the intent part). I encountered a similar problem.
With gfortran, there are three different dimension definition:
1. Fixed
2. Variable
3. Assumed-size
With ifort, categories 1 and 2 are considered the same, so you can do just define any dimension size as 0 in the interface and it works.
program test
implicit none
integer, dimension(:), allocatable :: ownlist
interface
subroutine blueprint(sz,arr)
integer, intent(in) :: sz
integer, dimension(0), intent(in) :: arr
! This zero means that the size does not matter,
! as long as it is a one-dimensional integer array.
end subroutine blueprint
end interface
procedure(blueprint), pointer :: ptr
allocate(ownlist(3))
ownlist = (/3,4,5/)
ptr => rout1
call ptr(3,ownlist)
deallocate(ownlist)
allocate(ownlist(0:10))
ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
ptr => rout2
call ptr(3,ownlist)
deallocate(ownlist)
contains
! This one has a dimension size as input.
subroutine rout1(sz,arr)
implicit none
integer, intent(in) :: sz
integer, dimension(sz), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout1
! This one has a fixed dimension size.
subroutine rout2(sz,arr)
implicit none
integer, intent(in) :: sz
integer, dimension(0:10), intent(in) :: arr
write(*,*) "Ignored integer: ",sz
write(*,*) arr
write(*,*) arr(1)
end subroutine rout2
end program test
Gfortran complains about the interface. Changing the 0 into 'sz' solves the problem four 'rout1', but not for 'rout2'.
However, you can fool gfortran around and say dimension(0:10+0*sz) instead of dimension(0:10) and gfortran compiles and gives the same
result as ifort.
This is a stupid trick and it relies on the existence of the integer 'sz' that may not be there. Another program:
program difficult_test
implicit none
integer, dimension(:), allocatable :: ownlist
interface
subroutine blueprint(arr)
integer, dimension(0), intent(in) :: arr
end subroutine blueprint
end interface
procedure(blueprint), pointer :: ptr
allocate(ownlist(3))
ownlist = (/3,4,5/)
ptr => rout1
call ptr(ownlist)
deallocate(ownlist)
allocate(ownlist(0:10))
ownlist = (/3,4,5,6,7,8,9,0,1,2,3/)
ptr => rout2
call ptr(ownlist)
deallocate(ownlist)
contains
subroutine rout1(arr)
implicit none
integer, dimension(3), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout1
subroutine rout2(arr)
implicit none
integer, dimension(0:10), intent(in) :: arr
write(*,*) arr
write(*,*) arr(1)
end subroutine rout2
end program difficult_test
This works under ifort for the same reasons as the previous example, but gfortran complains about the interface. I do not know how I can fix it.
The only thing I want to tell gfortran is 'I do not know the dimension size yet, but we will fix it.'. But this needs a spare integer arguemnt (or something else that we can turn into an integer) to fool gfortran around.

Pointing to a object's type variable - Fortran

As I understand, a user-derived type's definition can't contain target attributes. E.g., this isn't allowed:
type TestType
integer, target :: t
end type
However, it's fine for them to be a pointer:
type TestType2
integer, pointer :: p
end type
My question is, then, how can one use a pointer to point at an object's type variable? For example, if I wanted an object of type(TestType2) to have its p variable point to an object of type(TestType)'s t variable, how would I go about this? For example:
type(TestType) :: tt
type(TestType2) :: tt2
tt%t = 1
tt%p => tt%t
Thanks!
There would be very little sense in
type TestType
integer, target :: t
end type
because values of type(TestType) may easily come up in contexts where
they cannot be a target of a pointer.
As #roygvib comments, you have to give the target attribute to the whole object variable:
type(TestType), target :: tt
then you can make pointers to any of its components.
I could imagine that one could allow giving the target attribute to allocatable structure components in the type declaration, but it is not allowed. Certainly that would not make good sense for regular components.
Thanks #roygvib and #Vladimir F, I hadn't realised that giving the whole object variable the target attribute would allow me to point to any of its components. That worked perfectly.
For posterity, as my use case was a little more complex than the example above, I thought I'd post a more representative example of what I was trying to achieve. I was creating a grid system containing GridCells and Rivers, each GridCell having an array of Rivers, and each River also having an array of Rivers that flow into in (inflows) - these inflows would be Rivers that have been previously created and stored in the GridCell's array of rivers. I wanted to use pointers so that the inflows could just point to the corresponding river in a particular GridCell's rivers array.
The added complication is that River itself is an abstract type, extended by different SubRivers (SubRiver1 and SubRiver2 in the example below). I wanted the arrays of rivers and inflows to be of class(River) (i.e., polymorphic) and the only way to achieve that without Fortran complaining about polymorphic arrays was to create another user-derived type RiverElement with a polymorphic class(River), allocatable :: item property to store the river (see here).
Finally, because I couldn't set the inflows array such that each item was a pointer (setting inflows(:) as a pointer makes a pointer array, not an array of pointer), I had to create another user-derived type specifically for storing pointers to Rivers.
Here's the module with all the type definitions:
module TestModule
implicit none
type :: RiverPointer
class(River), pointer :: item => null()
end type
type, abstract :: River
type(RiverPointer), allocatable :: inflows(:)
integer :: id
end type
type :: RiverElement
class(River), allocatable :: item
end type
type :: GridCell
type(RiverElement), allocatable :: rivers(:)
end type
type, extends(River) :: SubRiver1
end type
type, extends(River) :: SubRiver2
end type
end module
And here's a test program showing that it works:
program main
use TestModule
implicit none
type(GridCell), target :: gc
type(SubRiver1) :: sr1
type(SubRiver2) :: sr2
type(SubRiver1) :: sr3
sr1%id = 1
sr2%id = 2
sr3%id = 3
allocate(gc%rivers(3))
allocate(gc%rivers(1)%item, source=sr1)
allocate(gc%rivers(2)%item, source=sr2)
allocate(gc%rivers(3)%item, source=sr3)
allocate(sr3%inflows(2))
sr3%inflows(1)%item => gc%rivers(1)%item
sr3%inflows(2)%item => gc%rivers(2)%item
write(*,*) sr3%inflows(1)%item%id ! 1
write(*,*) sr3%inflows(2)%item%id ! 2
gc%rivers(1)%item%id = 100
write(*,*) sr3%inflows(1)%item%id ! 100
end program
Thanks all!

Are anonymous arrays possible in fortran?

I am trying to create an array of arrays in Fortran.
Something like the following
TYPE :: array_of_arrays
REAL, DIMENSION(:), POINTER :: p => NULL()
END TYPE
TYPE(array_of_arrays), DIMENSION(2) :: some_array
So that I can do:
REAL, DIMENSION(3), TARGET :: some_vector1 = (/1.0, 2.1, 4.3/)
REAL, DIMENSION(3), TARGET :: some_vector2 = (/3.0, 1.2, 9.6/)
some_array(1)%p => some_vector1
some_array(2)%p => some_vector2
WRITE(*,*) some_array(1)%p ! I see some_vector1
WRITE(*,*) some_array(2)%p ! I see some_vector2
Now it's cumbersome for me to actually declare each of these some_vector arrays to correspond to each element in my array of arrays.
What I'd like to do is have in a separate subroutine where a temporary vector is set as a target, and that subroutine sets up my array of arrays to point to that temporary vector.
This way I can have anonymous arrays.
However, this doesn't seem to be working and I wonder if first if I am doing something that Fortran doesn't support.
So does Fortran support anonymous arrays, that is (in case I have the terms wrong), an array who can only be accessed through a reference?
Sure; as IanH suggests, you can just have the pointer refer to allocated memory directly, rather than refer to a variable; this is one of the few cases where the allocated memory doesn't automatically get deallocated once it goes out of scope.
eg,
module arrays
TYPE :: array_of_arrays
REAL, DIMENSION(:), POINTER :: p => NULL()
END TYPE
contains
subroutine alloc(aa)
type(array_of_arrays), intent(inout) :: aa(:)
integer :: i
allocate( aa(1)%p(1) )
aa(1) % p = [1.]
allocate( aa(2)%p(5) )
aa(2) % p = [ (i, i=1,5) ]
end subroutine alloc
end module arrays
program usearrays
use arrays
TYPE(array_of_arrays), DIMENSION(2) :: some_array
call alloc(some_array)
WRITE(*,*) some_array(1)%p ! I see some_vector1
WRITE(*,*) some_array(2)%p ! I see some_vector2
deallocate( some_array(1) )
deallocate( some_array(2) )
end program usearrays
and running it gives
$ gfortran -o arrays arrays.f90
$ ./arrays
1.0000000
1.0000000 2.0000000 3.0000000 4.0000000 5.0000000

Resources