Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
Announcements
FPGA community forums and blogs have moved to the Altera Community. Existing Intel Community members can sign in with their current credentials.

Memory storage of pointers

Arash_Rasekh
Beginner
1,415 Views

Hi.

I have a quastion about storage of pointers. i am working on data structure of a CFD program. There are some user defined types where need to point to other user defined types. in my old version, i used integers (or user defined types) to point array index of desierd user defined types. For example:

TYPE FACEFAM
INTEGER :: FACENUM
INTEGER :: FACTYPE 
INTEGER :: PARNUM
TYPE (PARENT),ALLOCATABLE :: PARENTS(:)
INTEGER ,ALLOCATABLE :: NODES(:)
REAL(8) :: AREA
REAL(8), DIMENSION(3) :: NORMAL
REAL(8), DIMENSION(3) :: R
END TYPE FACEFAM

! FACE

TYPE FACE
INTEGER :: FACENUM
INTEGER :: FACTYPE 
INTEGER ,ALLOCATABLE :: NODES(:)
REAL(8) :: NORSGN=0.D0
LOGICAL :: BND=.FALSE.
INTEGER :: BNDSET
INTEGER :: BNDNUM

END TYPE FACE

TYPE ELEMENT
INTEGER :: ELMNUM
INTEGER :: ELMTYP
INTEGER :: NUMNOD
INTEGER,ALLOCATABLE :: ELMNOD(:)
INTEGER :: NUMEDG
INTEGER :: NUMFAC
INTEGER :: NUMBND=0
INTEGER :: NUMNEIGH
TYPE(EDGE),ALLOCATABLE :: EDGES(:)
TYPE(FACE),ALLOCATABLE :: FACES(:)  !!!!!!!!!!!! note to thistype.+++++++++++++++++++++++++++++++++++++++++++++++++ 
INTEGER,ALLOCATABLE :: ELMNIG(:) 
REAL(8) :: CENTROID(3)
REAL(8) :: VOLUME
LOGICAL :: LOGFLG=.FALSE. ! LOGICAL FLAG
INTEGER,ALLOCATABLE :: STENCIL(:)
REAL(8),ALLOCATABLE :: AP(:,:)
REAL(8),ALLOCATABLE :: D(:)
REAL(8),ALLOCATABLE :: INTG(:)

END TYPE ELEMENT

! CALCULATING ELEMENTS VOLUME
I=0.D0
V=0.D0
DO I=1,MESHDATA.SPEC.NUMELM
W=0.D0
C(1:3)=0.D0
DO J=1,MESHDATA.ELEMENTS(I).NUMFAC
M=MESHDATA.ELEMENTS(I).FACES(J).FACENUM
S=(MESHDATA.ELEMENTS(I).FACES(J).NORSGN)*(MESHDATA.FACES(M).AREA)*(MESHDATA.FACES(M).NORMAL)
R=MESHDATA.FACES(M).R
W=(S(1)*R(1)+S(2)*R(2)+S(3)*R(3))+W
C=(S(1)*R(1)+S(2)*R(2)+S(3)*R(3))*R+C
CONTINUE
END DO
MESHDATA.ELEMENTS(I).VOLUME=W/3.D0
MESHDATA.ELEMENTS(I).CENTROID=C/W*3.D0/4.D0
V=W+V
END DO
MESHDATA.SPEC.VOLUME=V

Now, i want to use pointers to simplifiy the redirections (and also other advantages of pointers). for exapmle (types are not complete yet) :

type,abstract :: type_face_base
integer :: surface_number
integer :: surface_type
integer :: parent_number
real(wp) :: area
logical :: flag=.false.
class(type_node_2d),pointer :: nodes(:)
class(type_vector_2d),allocatable :: normal
class(type_vector_2d),allocatable :: centroid
end type type_face_base

type :: type_face_container
class(type_face_base),pointer :: face
end type type_face_container

type,extends(type_face_base) :: type_face_triangle

end type type_face_triangle

type,abstract :: type_element_base
integer :: element_number
integer :: number_of_boundaries=0
integer :: number_of_neighbors
integer,allocatable :: neighbors(:)
real(wp) :: volume
class(type_node_2d),pointer :: nodes(:)=>null()
class(type_face_container),allocatable :: faces(:)   !!!!!! note to thistype.+++++++++++++++++++++++++++++++++++++++++++++++++
class(type_vector_2d),allocatable :: centroid
logical :: flag=.false. ! logical flag
integer,allocatable :: stencil(:)
real(wp),allocatable :: aplus(:,:)
real(wp),allocatable :: d(:)
real(wp),allocatable :: geometric_moments(:)
contains
procedure(interface_initiate),deferred :: initiate
end type type_element_base

I want to know about memory usage of pointers. Does their memory usage is in order of default integers or they use more memory due to their declared type?

Sorry for bad english.

Thanks.

0 Kudos
7 Replies
TimP
Honored Contributor III
1,415 Views
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,415 Views
TimP Have the documentation people revise: "•The remaining bytes (24 to 107) contain information about each dimension (up to 31). Each dimension is described by a set of 3 4-byte entities" Change 107 to 396. 107 is the extent for 7 dimensions (old upper limit for dimensions). With 31 dimensions we get: (6 + 3*31)*4 = 396 The above for x32 Jim Dempsey
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,415 Views
TimP, Also have the documentation explain what they mean by the "base address". The C/C++ newbies to array descriptors will be confused. The base address is the address of where the 0'th element of the array would be had the array been allocated with a lower bound of 0. This is not necessarily the address of the allocation (in most cases it is not, since default array indecies start at 1). Example, on x32 allocate(A(10)) would allocate A(1:10). The base address is the location of A(0), which is an invalid address since it is allocated address - 4. For the C/C++ programmers, this "hack" eliminates subtracting the lower bound from every array access (i.e. performance hack) Jim Dempsey
0 Kudos
Arash_Rasekh
Beginner
1,415 Views
Thanks for your answers.
0 Kudos
Steven_L_Intel1
Employee
1,415 Views
Jim, the base address is the same as what C programmers mean by it - the lowest addressed storage unit. We don't use the "A0 address" anymore. I will have the documentation corrected on the size of the bounds information - we missed that when revising this chapter.
0 Kudos
jimdempseyatthecove
Honored Contributor III
1,415 Views
>> the base address is the same as what C programmers mean by it - the lowest addressed storage unit. We don't use the "A0 address" anymore. Good to know. Though it adds a little overhead (subtracting lower bound from index) In C++ new Array (array allocations), the allocation adds a size_t element in front of the array for count of items, but returns the location following the count for the address of the array. Does the newer FORTRAN allocation include a number of elements prepended to the array data? Jim Dempsey
0 Kudos
Steven_L_Intel1
Employee
1,415 Views
Any data about allocation size is kept separately and is not user-accessible, except in the descriptor. You can of course use Fortran intrinsics such as SIZE to get number of elements. There is an approved Technical Specification for "Enhanced C interoperability" that provides mechanisms to exchange arrays, including allocatable arrays, between Fortran and C. This will be part of the next Fortran standard (called Fortran 2015.)
0 Kudos
Reply