Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Force a derived type pointer to point to intrinsic data type array.

lostInLimbo
Beginner
861 Views

I work in an old code where an array is passed in to my routine. The array follows a data structure. I want to define a derived type similar to the data structure and  point it to the array. I tried this and it gives a data type mismatch error(understandably so). Is there a way I can do this without copying the data?

Example code:

{

subroutine test(a,size)

implicit none

integer,target,intent(in) :: a(*)

integer,intent(in) :: size

! defined in module

!type data_struct

! sequence

! integer d

! integer e

! integer f

!end type data_struct

type(data_struct),pointer :: temp_struct(:)

temp_struct=>a(1:size)

}

I want to do something like above where I can create an array of temp_struct derived data types pointing to the existing array. I tried to do it various ways but the only solution that worked for me was by copying the data, which I don't want to do.

Any comments and suggestions are welcome. Thanks.

 

0 Kudos
1 Solution
FortranFan
Honored Contributor II
861 Views

lostInLimbo wrote:

Quote:

FortranFan wrote:

 

Care to explain in detail what you mean by "The array follows a data structure"?

 

 

It's similar to my example code. I have a set of values like id followed by related values repeated for the whole model like,

id1, param1_x, param1_y, param1_z, id2, param2_x, param2_y, param2_z,............paramN_z

Here N can potentially be a very large number. The thing is there are many such arrays with various model specific data (different data structures) throughout. EQUIVALENCE is used quite liberally in the old code and many places array has mixed integer, real values. I am not worried about mixed data types for now but was wondering if I can enforce a derived type onto it without copying so that I can access the data like follows

    derived_type_for_param(1)%id
    derived_type_for_param(1)%param_x
    derived_type_for_param(1)%param_y
    derived_type_for_param(1)%param_z

So are you just looking for a convenient way to work with such an array of repeated values (and where the number of repeats N can be large)?  Or does it really have to be mapped to a Fortran derived type the way you indicate?

In other words, are you ok if the access method is, say, derived_type_for_param%param_x(i) instead of derived_type_for_param(1)%param_x?  If so, an immediate thought that comes to mind is the ability to add procedures that are "bound" to the derived type and where the procedure is a function with a result that is a pointer to the data of interest.  See below.  And with the Fortran 2008 standard revision that allows a pointer function in a variable definition context, the access to the data can be as read and write!

module data_m
   implicit none
   private
   type, public :: data_t
      private
      integer, pointer :: data(:) => null()
   contains
      private
      procedure, pass(this), public :: set_data
      procedure, pass(this), public :: id
      procedure, pass(this), public :: param_x
      procedure, pass(this), public :: param_y
      procedure, pass(this), public :: param_z
   end type
contains
   subroutine set_data( this, data )
      class(data_t), intent(inout) :: this
      integer, target, intent(in)  :: data(:)
      this%data => data
   end subroutine
   function id( this, idx ) result( pid )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: pid
      ! Handling elided for invalid idx
      pid => this%data((idx-1)*4+1)
   end function
   function param_x( this, idx ) result( px )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: px
      ! Handling elided for invalid idx
      px => this%data((idx-1)*4+2)
   end function
   function param_y( this, idx ) result( py )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: py
      ! Handling elided for invalid idx
      py => this%data((idx-1)*4+3)
   end function
   function param_z( this, idx ) result( pz )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: pz
      ! Handling elided for invalid idx
      pz => this%data((idx-1)*4+4)
   end function
end module
program p
   use data_m, only : data_t
   implicit none
   type(data_t) :: dt
   integer, allocatable, target :: some_data(:)
   integer :: i
   character(len=*), parameter :: fmtd = "(g0,t10,g0,t20,g0,t30,g0)"
   some_data = [ 101, 141, 142, 143, &
                 201, 241, 242, 243, &
                 301, 341, 343, 343 ]
   call dt%set_data( some_data )
   print *, "derived_type_for_param"
   print fmtd, "id", "param_x", "param_y", "param_z"
   do i = 1, size(some_data)/4
      print fmtd, dt%id(i), dt%param_x(i), dt%param_y(i), dt%param_z(i)
   end do
   ! Values can be changed too
   do i = 1, size(some_data)/4
      dt%param_x(i) = -dt%param_x(i)
      dt%param_y(i) = -dt%param_y(i)
      dt%param_z(i) = -dt%param_z(i)
   end do
   print *, "After changes to the value"
   print fmtd, "id", "param_x", "param_y", "param_z"
   do i = 1, size(some_data)/4
      print fmtd, dt%id(i), dt%param_x(i), dt%param_y(i), dt%param_z(i)
   end do
   stop
end program

Upon execution using Intel Fortran 19.0 compiler Update 1, the output is:

 derived_type_for_param
id       param_x   param_y   param_z
101      141       142       143
201      241       242       243
301      341       343       343
 After changes to the value
id       param_x   param_y   param_z
101      -141      -142      -143
201      -241      -242      -243
301      -341      -343      -343

Is this what you are looking for? 

View solution in original post

0 Kudos
9 Replies
lostInLimbo
Beginner
861 Views

I couldn't see this post in my activity and I thought I lost it. I asked this same question in stackoverflow and got some responses

https://stackoverflow.com/questions/54347558/is-it-possible-to-point-a-fortran-derived-data-type-pointer-to-intrinsic-data-ty

Any additional comments/suggestions are welcome.

 

0 Kudos
FortranFan
Honored Contributor II
861 Views

Care to explain in detail what you mean by "The array follows a data structure"?

0 Kudos
lostInLimbo
Beginner
861 Views

FortranFan wrote:

Care to explain in detail what you mean by "The array follows a data structure"?

It's similar to my example code. I have a set of values like id followed by related values repeated for the whole model like,

id1, param1_x, param1_y, param1_z, id2, param2_x, param2_y, param2_z,............paramN_z

Here N can potentially be a very large number. The thing is there are many such arrays with various model specific data (different data structures) throughout. EQUIVALENCE is used quite liberally in the old code and many places array has mixed integer, real values. I am not worried about mixed data types for now but was wondering if I can enforce a derived type onto it without copying so that I can access the data like follows

    derived_type_for_param(1)%id
    derived_type_for_param(1)%param_x
    derived_type_for_param(1)%param_y
    derived_type_for_param(1)%param_z

0 Kudos
jimdempseyatthecove
Honored Contributor III
861 Views
module foo
type derived_type_for_param_t
  integer :: id
  real :: param_x, parm_y, parm_z
end type derived_type_for_param_t

integer, parameter :: extend_derived_type_for_param_by = 10000
integer :: number_of_used_derived_type_for_param
type(derived_type_for_param_t), allocatable :: derived_type_for_param(:)

end module foo
...
subroutine append_derived_type_for_param(id, param_x, parm_y, parm_z)
  use foo
  integer, intent(in) :: id
  real, intent(in) :: param_x, parm_y, parm_z
  type(derived_type_for_param_t), allocatable :: temp_derived_type_for_param(:)

  if(.not.allocated(derived_type_for_param)) then
    allocate(derived_type_for_param(extend_derived_type_for_param_by))
    number_of_used_derived_type_for_param = 1
  else
    if(number_of_used_derived_type_for_param == size(derived_type_for_param)) then
      allocate(temp_derived_type_for_param(size(derived_type_for_param) + extend_derived_type_for_param_by))
      temp_derived_type_for_param(1:size(derived_type_for_param)) = derived_type_for_param
      call move_alloc(temp_derived_type_for_param, derived_type_for_param) 
    endif
    number_of_used_derived_type_for_param = number_of_used_derived_type_for_param + 1
  endif
  derived_type_for_param(number_of_used_derived_type_for_param)%id = id
  derived_type_for_param(number_of_used_derived_type_for_param)%param_x = parm_x
  derived_type_for_param(number_of_used_derived_type_for_param)%param_y = parm_y
  derived_type_for_param(number_of_used_derived_type_for_param)%param_z = parm_z
end subroutine append_derived_type_for_param

Something like the above

Jim Dempsey

0 Kudos
FortranFan
Honored Contributor II
862 Views

lostInLimbo wrote:

Quote:

FortranFan wrote:

 

Care to explain in detail what you mean by "The array follows a data structure"?

 

 

It's similar to my example code. I have a set of values like id followed by related values repeated for the whole model like,

id1, param1_x, param1_y, param1_z, id2, param2_x, param2_y, param2_z,............paramN_z

Here N can potentially be a very large number. The thing is there are many such arrays with various model specific data (different data structures) throughout. EQUIVALENCE is used quite liberally in the old code and many places array has mixed integer, real values. I am not worried about mixed data types for now but was wondering if I can enforce a derived type onto it without copying so that I can access the data like follows

    derived_type_for_param(1)%id
    derived_type_for_param(1)%param_x
    derived_type_for_param(1)%param_y
    derived_type_for_param(1)%param_z

So are you just looking for a convenient way to work with such an array of repeated values (and where the number of repeats N can be large)?  Or does it really have to be mapped to a Fortran derived type the way you indicate?

In other words, are you ok if the access method is, say, derived_type_for_param%param_x(i) instead of derived_type_for_param(1)%param_x?  If so, an immediate thought that comes to mind is the ability to add procedures that are "bound" to the derived type and where the procedure is a function with a result that is a pointer to the data of interest.  See below.  And with the Fortran 2008 standard revision that allows a pointer function in a variable definition context, the access to the data can be as read and write!

module data_m
   implicit none
   private
   type, public :: data_t
      private
      integer, pointer :: data(:) => null()
   contains
      private
      procedure, pass(this), public :: set_data
      procedure, pass(this), public :: id
      procedure, pass(this), public :: param_x
      procedure, pass(this), public :: param_y
      procedure, pass(this), public :: param_z
   end type
contains
   subroutine set_data( this, data )
      class(data_t), intent(inout) :: this
      integer, target, intent(in)  :: data(:)
      this%data => data
   end subroutine
   function id( this, idx ) result( pid )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: pid
      ! Handling elided for invalid idx
      pid => this%data((idx-1)*4+1)
   end function
   function param_x( this, idx ) result( px )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: px
      ! Handling elided for invalid idx
      px => this%data((idx-1)*4+2)
   end function
   function param_y( this, idx ) result( py )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: py
      ! Handling elided for invalid idx
      py => this%data((idx-1)*4+3)
   end function
   function param_z( this, idx ) result( pz )
      class(data_t), intent(in) :: this
      integer, intent(in)       :: idx
      ! Function result
      integer, pointer :: pz
      ! Handling elided for invalid idx
      pz => this%data((idx-1)*4+4)
   end function
end module
program p
   use data_m, only : data_t
   implicit none
   type(data_t) :: dt
   integer, allocatable, target :: some_data(:)
   integer :: i
   character(len=*), parameter :: fmtd = "(g0,t10,g0,t20,g0,t30,g0)"
   some_data = [ 101, 141, 142, 143, &
                 201, 241, 242, 243, &
                 301, 341, 343, 343 ]
   call dt%set_data( some_data )
   print *, "derived_type_for_param"
   print fmtd, "id", "param_x", "param_y", "param_z"
   do i = 1, size(some_data)/4
      print fmtd, dt%id(i), dt%param_x(i), dt%param_y(i), dt%param_z(i)
   end do
   ! Values can be changed too
   do i = 1, size(some_data)/4
      dt%param_x(i) = -dt%param_x(i)
      dt%param_y(i) = -dt%param_y(i)
      dt%param_z(i) = -dt%param_z(i)
   end do
   print *, "After changes to the value"
   print fmtd, "id", "param_x", "param_y", "param_z"
   do i = 1, size(some_data)/4
      print fmtd, dt%id(i), dt%param_x(i), dt%param_y(i), dt%param_z(i)
   end do
   stop
end program

Upon execution using Intel Fortran 19.0 compiler Update 1, the output is:

 derived_type_for_param
id       param_x   param_y   param_z
101      141       142       143
201      241       242       243
301      341       343       343
 After changes to the value
id       param_x   param_y   param_z
101      -141      -142      -143
201      -241      -242      -243
301      -341      -343      -343

Is this what you are looking for? 

0 Kudos
lostInLimbo
Beginner
861 Views

@JimDempsey Thanks for the example code. I was wondering wouldn't it create equal number of pointers as the data in the array itself? Essentially occupying similar amount of memory or am i looking at it wrong?

0 Kudos
lostInLimbo
Beginner
861 Views

@FortranFan you are right I am just looking for a convenient way to work with the array. I am not very familiar with fortran 2008 standard. I mostly understand your code but I am not sure how "idx" gets it's value. Also does one pointer for say param_x point to all param_x values?

Also on unrelated note my understanding is when a pointer points to a array it stores the bounds and stride of the array and location, essentially one pointer is used to access the whole array rather than one pointer per element of the pointed array/subarray. Is that correct? I couldn't find a clear answer anywhere.

0 Kudos
FortranFan
Honored Contributor II
861 Views

lostInLimbo wrote:

@FortranFan you are right I am just looking for a convenient way to work with the array. I am not very familiar with fortran 2008 standard. I mostly understand your code but I am not sure how "idx" gets it's value. Also does one pointer for say param_x point to all param_x values?

Also on unrelated note my understanding is when a pointer points to a array it stores the bounds and stride of the array and location, essentially one pointer is used to access the whole array rather than one pointer per element of the pointed array/subarray. Is that correct? I couldn't find a clear answer anywhere.

@lostInLimbo,

You wrote the data of interest to you are organized as:

id1, param1_x, param1_y, param1_z, id2, param2_x, param2_y, param2_z,............paramN_z

indicating N sets of values.  Further your comments indicated you were hoping to access them in your code as derived_type_for_param(1)%id, derived_type_for_param(1)%param_x, etc.,which suggested your plan to use an 'indexer', say i, that might go from 1 to N, though you only showed an index of 1 in your snippet.

So basically what I did is set up the so-called indexer-based accessor functions (id, param_x, etc.) which return a pointer to an element of your data.  Its functioning makes it appear as if you are working with an element of an ordinary array in Fortran, particularly since it can be present in a variable-definition context.

So putting all else aside, especially the whole array operations starting with Fortran 90, the data structure essentially takes your data and sets it up as 4 "virtual" arrays - id, param_x, param_y, and param_z- and which you access as dt%id(i) or dt%param_y(j), etc. and where the indices i and j are defined somehow in the calling code (e.g., DO I = 1, N; .. dt%param_X(I) .. ; .. END DO), just as you would if you were dealing 4 such arrays in good old-fashioned FORTRAN 77 (and older) code.  And note this is all achieved via the data_t derived type WITHOUT ANY COPYING whatsoever.

Separately, on your question re: variables with the POINTER attribute in Fortran, note such a variable can be given a rank also with the DIMENSION attribute.  Thus a variable of POINTER attribute in Fortran with rank 0 i.e, no DIMENSION attribute implies a scalar which points to an object of the same rank which can be a scalar TARGET itself or one element of an array TARGET, etc.  A variable with POINTER and DIMENSION of rank 1 (e.g., 1D array) can point to an object with rank 1 which can be another 1D array TARGET or a row/column of a 2D array TARGET, etc.  In the data_t derived type I have showed you, the component of the derived type 'data' has the POINTER attribute and it has rank 1.  Whereas the results of the 4 accessor functions have the POINTER attribute but they are of rank 0, so they will point to some rank 0 target only.

0 Kudos
lostInLimbo
Beginner
861 Views

@FortranFan Thanks for the detailed explanation.

0 Kudos
Reply