Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

getting offset of allocatable derived types

27 views
Skip to first unread message

hatings...@gmail.com

unread,
Jan 5, 2009, 5:02:37 PM1/5/09
to
I have the following test code that returns the offset of a derived
type that has an allocatable array as one of its components. It
returns 48, 72, and 64 for gfortran, ifort and g95 respectively. If I
make the "sensors" array non-allocatable then it returns the expected
result of 8 (assuming integer*4) for all the mentioned compilers. Can
I not use the C_LOC function and get the correct pointer address when
a structure contains an allocatable array. If not, then is there some
portable way of doing it.

PROGRAM main

USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE

TYPE vehicle_t1
INTEGER(C_INT), DIMENSION(:), ALLOCATABLE :: sensors
END TYPE vehicle_t1
TYPE(vehicle_t1), DIMENSION(1:2), TARGET :: walloc
TYPE(C_PTR) :: f_ptr3, f_ptr4

INTERFACE
INTEGER(C_INTPTR_T) FUNCTION h5offsetof(start,end) RESULT(offset)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
TYPE(C_PTR), VALUE, INTENT(IN) :: start, end
END FUNCTION h5offsetof
END INTERFACE

ALLOCATE(walloc(1)%sensors(1:2))
ALLOCATE(walloc(2)%sensors(1:2))

f_ptr3 = C_LOC(walloc(1))
f_ptr4 = C_LOC(walloc(2))

! does not work either
! f_ptr3 = C_LOC(walloc(1)%sensors(1))
! f_ptr4 = C_LOC(walloc(2)%sensors(1))

PRINT*,'H5OFFSETOF', H5OFFSETOF(f_ptr3,f_ptr4)

END PROGRAM main

INTEGER(C_INTPTR_T) FUNCTION h5offsetof(start,end) RESULT(offset)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
TYPE(C_PTR), VALUE, INTENT(IN) :: start, end

INTEGER(C_INTPTR_T) :: address_start, address_end
address_start = TRANSFER(start, address_start)
address_end = TRANSFER(end , address_end )

offset = address_end - address_start
END FUNCTION h5offsetof

Richard Maine

unread,
Jan 5, 2009, 10:01:52 PM1/5/09
to
<hatings...@gmail.com> wrote:

> I have the following test code that returns the offset of a derived
> type that has an allocatable array as one of its components. It
> returns 48, 72, and 64 for gfortran, ifort and g95 respectively. If I
> make the "sensors" array non-allocatable then it returns the expected
> result of 8 (assuming integer*4) for all the mentioned compilers. Can
> I not use the C_LOC function and get the correct pointer address when
> a structure contains an allocatable array. If not, then is there some
> portable way of doing it.

[Code elided]

It isn't clear to me what you are trying to do and what you expect. Note
first that a derived type with an allocatable component is not
interoperable.

Second, it seems to me that you are making seriously incorrect
assumptions about how allocatable components work. Are you expecting to
see that the offsets will vary depending on the allocated size of the
allocatable components? That is not so, and can't plausibly be so. The
offset between two elements of a contiguous array is a constant for a
particular type. It does not depend on the values of components or such
things as the allocated size of allocatable components, or indeed on
anything other than the type and type parameters. Anything else would be
completely unworkable. The compiler couldn't do simple index
computations to find the element locations.... and life would get even
more complicated when elements in the middle of the array changed sizes.

I'm pretty confident that you are getting the correct locations. I'm not
so convinced that your expectations are plausible. Perhaps I'm
misguessing what you expect, as I'm having to deduce it a bit.

For an allocatable component, the fixed-size derived-type element will
contain some kind of descriptor, which gives information about the size
and location of the allocatable data. The details of that descriptor are
compiler dependent. The actual allocatable data will be somewhere
"else", pointed to by the descriptor.

--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain

Craig Powers

unread,
Jan 5, 2009, 10:22:23 PM1/5/09
to
hatings...@gmail.com wrote:
> I have the following test code that returns the offset of a derived
> type that has an allocatable array as one of its components. It
> returns 48, 72, and 64 for gfortran, ifort and g95 respectively. If I
> make the "sensors" array non-allocatable then it returns the expected
> result of 8 (assuming integer*4) for all the mentioned compilers. Can
> I not use the C_LOC function and get the correct pointer address when
> a structure contains an allocatable array. If not, then is there some
> portable way of doing it.

Keep in mind that allocatable arrays wind up being implemented as a
descriptor that contains some sort of reference to the memory block of
the array data (as well as other information about the bounds of the
array), and those descriptors are implementation-specific.
Consequently, the behavior you observe is the behavior that I would
expect: it's impossible to get a portable derived type layout if that
derived type contains an allocatable (or a pointer). As in C++, the
only way to get a portable layout is with a POD type.

James Van Buskirk

unread,
Jan 6, 2009, 5:40:52 AM1/6/09
to
"Richard Maine" <nos...@see.signature> wrote in message
news:1it32v4.1pfasuk8yoygN%nos...@see.signature...

> I'm pretty confident that you are getting the correct locations. I'm not
> so convinced that your expectations are plausible. Perhaps I'm
> misguessing what you expect, as I'm having to deduce it a bit.

To add to your discussion, the commented-out attempt would perform
as the O.P. expects if only allocations were contiguous and
consecutive. They are not, but he could get contiguous and consecutive
memory by using pointer components instead of allocatable components,
allocating a big array, and pointing the pointer components at the
array:

C:\Program Files\Microsoft Visual Studio 8\James\clf\correct_ptr>type
correct_pt
r.f90
PROGRAM main

USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE

TYPE vehicle_t1
INTEGER(C_INT), DIMENSION(:), POINTER :: sensors


END TYPE vehicle_t1
TYPE(vehicle_t1), DIMENSION(1:2), TARGET :: walloc
TYPE(C_PTR) :: f_ptr3, f_ptr4

integer sizes(size(walloc))
integer(C_INT), allocatable, target :: dat(:)
integer i

INTERFACE
INTEGER(C_INTPTR_T) FUNCTION h5offsetof(start,end) RESULT(offset)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
TYPE(C_PTR), VALUE, INTENT(IN) :: start, end
END FUNCTION h5offsetof
END INTERFACE

! ALLOCATE(walloc(1)%sensors(1:2))
! ALLOCATE(walloc(2)%sensors(1:2))
sizes(1) = 2
sizes(2) = 2
allocate(dat(sum(sizes)))
do i = 1, size(walloc)
walloc(i)%sensors => dat(sum(sizes(1:i-1))+1:sum(sizes(1:i)))
end do

! f_ptr3 = C_LOC(walloc(1))
! f_ptr4 = C_LOC(walloc(2))

! now this works
f_ptr3 = C_LOC(walloc(1)%sensors(1))
f_ptr4 = C_LOC(walloc(2)%sensors(1))

PRINT*,'H5OFFSETOF', H5OFFSETOF(f_ptr3,f_ptr4)

END PROGRAM main

INTEGER(C_INTPTR_T) FUNCTION h5offsetof(start,end) RESULT(offset)
USE, INTRINSIC :: ISO_C_BINDING
IMPLICIT NONE
TYPE(C_PTR), VALUE, INTENT(IN) :: start, end

INTEGER(C_INTPTR_T) :: address_start, address_end
address_start = TRANSFER(start, address_start)
address_end = TRANSFER(end , address_end )

offset = address_end - address_start
END FUNCTION h5offsetof

C:\Program Files\Microsoft Visual Studio 8\James\clf\correct_ptr>gfortran
correc
t_ptr.f90 -ocorrect_ptr

C:\Program Files\Microsoft Visual Studio 8\James\clf\correct_ptr>correct_ptr
H5OFFSETOF 8

--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end


hatings...@gmail.com

unread,
Jan 6, 2009, 1:59:05 PM1/6/09
to
On Jan 5, 9:22 pm, Craig Powers <craig.pow...@invalid.invalid> wrote:

Just to elaborate, I'm trying to write a function for HDF to easily
obtain the size of a derived data type. Many functions require the
number of bytes in the datatype to be registered. Normally this is
done with sizeof in C but since there is no equivalent in Fortran I
have to improvise. The function is to get the offset in memory
structure of the datatype similar to the C macro offsetof:

For example, if I have the datatype

TYPE sensor_t ! Nested compound type
INTEGER*4 :: serial_no
CHARACTER(LEN=80) :: location
REAL*8 :: temperature
REAL*8 :: pressure
END TYPE sensor_t

the offset would be something like 0,4, 88, 96 for serial_no,
location, temperature, pressure respectively, depending on the
machine's native settings for the structure in memory.
Now if I have

TYPE(sensor_t), DIMENSION(1:2), TARGET :: wdata

and find the offset between wdata(1) and wdata(2) this would give the
sizeof sensor_t. It appears that this does not work for allocatable
arrays as mentioned. I'll try using the pointer work around that James
mentioned but I think for complicated nested derived types that would
defeat the purpose of having a function to simplify things.
Thanks for the help.

Richard Maine

unread,
Jan 6, 2009, 7:32:05 PM1/6/09
to
<hatings...@gmail.com> wrote:

> and find the offset between wdata(1) and wdata(2) this would give the
> sizeof sensor_t. It appears that this does not work for allocatable
> arrays as mentioned.

No, it works fine and does get you the size in question. I think you
don't yet understand that the problem is far more fundamental. It is not
just a matter of computing some size.

The actual data for the allocatable component is stored "elsewhere" in
memory. If you are trying to send an object with such a componen via
something like HDF or anything else that wants to send a contiguous
chunck of memory (i.e. anything that doesn't explicitly know details
about the implementation of the particular type in question), then it
isn't going to work at all. The size isn't the problem. The assumption
that all the data is contiguously stored in *ANY* size is the problem.

James Van Buskirk

unread,
Jan 7, 2009, 12:00:36 AM1/7/09
to
"Richard Maine" <nos...@see.signature> wrote in message
news:1it4r1r.udne3hbrqgeqN%nos...@see.signature...

> <hatings...@gmail.com> wrote:

>> and find the offset between wdata(1) and wdata(2) this would give the
>> sizeof sensor_t. It appears that this does not work for allocatable
>> arrays as mentioned.

> No, it works fine and does get you the size in question. I think you
> don't yet understand that the problem is far more fundamental. It is not
> just a matter of computing some size.

> The actual data for the allocatable component is stored "elsewhere" in
> memory. If you are trying to send an object with such a componen via
> something like HDF or anything else that wants to send a contiguous
> chunck of memory (i.e. anything that doesn't explicitly know details
> about the implementation of the particular type in question), then it
> isn't going to work at all. The size isn't the problem. The assumption
> that all the data is contiguously stored in *ANY* size is the problem.

Although your remarks have been consistent with your high standards in
this thread, nonetheless I feel the urge to again interpret the O.P.'s
query slightly differently and to respond with an example:

C:\gfortran\clf\sizetest>type sizetest.f90
program sizetest
use ISO_C_BINDING
implicit none
integer, parameter :: ik1 = selected_int_kind(2)


TYPE vehicle_t1
INTEGER(C_INT), DIMENSION(:), ALLOCATABLE :: sensors
END TYPE vehicle_t1

type(vehicle_t1) gfortran_bug_workaround

allocate(gfortran_bug_workaround%sensors(2))
! write(*,*) size(transfer(vehicle_t1(NULL()),[0_ik1]))
write(*,*) size(transfer(gfortran_bug_workaround,[0_ik1]))
write(*,*) 'made it here...'
write(*,*) C_SIZEOF(vehicle_t1(NULL()))
end program sizetest

C:\gfortran\clf\sizetest>gfortran sizetest.f90 -osizetest

C:\gfortran\clf\sizetest>sizetest
48
made it here...
48

So we can see that there are two standard flavors of SIZEOF, the
one with TRANSFER dating back to f90 and the one with C_SIZEOF
requiring f03.

WARNING: at least in old versions of gfortran C_SIZEOF is the same
as its SIZEOF extension and doesn't have Fortran semantics. I was
trying to denonstrate an example of this but ran afoul of another
ICE:

C:\gfortran\clf\sizetest>type sizeof.f90
module funcs
implicit none
contains
recursive function returns_true(depth)
logical returns_true
integer depth
type dud
integer x
end type dud
integer y(C_SIZEOF(dud(0)))
save

y = 1
if(depth > 0) then
y = 0
returns_true = helpme(depth-1)
end if
returns_true = y(1) == 0
end function returns_true

recursive function helpme(x)
integer x
logical helpme

helpme = returns_true(x)
end function helpme
end module funcs

program sizeof_test
use funcs
implicit none

write(*,*) returns_true(1)
end program sizeof_test

C:\gfortran\clf\sizetest>gfortran -v
Built by Equation Solution (http://www.Equation.com).
Using built-in specs.
Target: x86_64-pc-mingw32
Configured with:
../gcc-4.4-20081212-mingw/configure --host=x86_64-pc-mingw32 --
build=x86_64-unknown-linux-gnu --target=x86_64-pc-mingw32 --prefix=/home/gfortra
n/gcc-home/binary/mingw32/native/x86_64/gcc/4.4-20081212 --with-gmp=/home/gfortr
an/gcc-home/binary/mingw32/native/x86_64/gmp --with-mpfr=/home/gfortran/gcc-home
/binary/mingw32/native/x86_64/mpfr --with-sysroot=/home/gfortran/gcc-home/binary
/mingw32/cross/x86_64/gcc/4.4-20081212 --with-gcc --with-gnu-ld --with-gnu-as
--
disable-shared --disable-nls --disable-tls --enable-libgomp --enable-languages=c
,fortran --enable-threads=win32 --disable-win32-registry
Thread model: win32
gcc version 4.4.0 20081212 (experimental) (GCC)

C:\gfortran\clf\sizetest>gfortran sizeof.f90
sizeof.f90: In function 'returns_true':
sizeof.f90:10: internal compiler error: in gfc_trans_auto_array_allocation,
at f
ortran/trans-array.c:4157
Please submit a full bug report,
with preprocessed source if appropriate.
See <http://gcc.gnu.org/bugs.html> for instructions.

Oh well, enough fun for this post :)

James Van Buskirk

unread,
Jan 7, 2009, 12:05:15 AM1/7/09
to
"James Van Buskirk" <not_...@comcast.net> wrote in message
news:gk1ctm$5f2$1...@news.motzarella.org...

> C:\gfortran\clf\sizetest>type sizetest.f90
> program sizetest
> use ISO_C_BINDING
> implicit none
> integer, parameter :: ik1 = selected_int_kind(2)
> TYPE vehicle_t1
> INTEGER(C_INT), DIMENSION(:), ALLOCATABLE :: sensors
> END TYPE vehicle_t1
> type(vehicle_t1) gfortran_bug_workaround
>
> allocate(gfortran_bug_workaround%sensors(2))
> ! write(*,*) size(transfer(vehicle_t1(NULL()),[0_ik1]))
> write(*,*) size(transfer(gfortran_bug_workaround,[0_ik1]))
> write(*,*) 'made it here...'
> write(*,*) C_SIZEOF(vehicle_t1(NULL()))
> end program sizetest

I failed to use the most recent version above:

program sizetest
use ISO_C_BINDING
implicit none
integer, parameter :: ik1 = selected_int_kind(2)
TYPE vehicle_t1
INTEGER(C_INT), DIMENSION(:), ALLOCATABLE :: sensors
END TYPE vehicle_t1
type(vehicle_t1) gfortran_bug_workaround

! Oog, serious bugginess: gfortran dies @ runtime if the following
! line is omitted, and fails to compile the commented-out line.


allocate(gfortran_bug_workaround%sensors(2))
! write(*,*) size(transfer(vehicle_t1(NULL()),[0_ik1]))
write(*,*) size(transfer(gfortran_bug_workaround,[0_ik1]))
write(*,*) 'made it here...'
write(*,*) C_SIZEOF(vehicle_t1(NULL()))
end program sizetest

> C:\gfortran\clf\sizetest>gfortran sizetest.f90 -osizetest

> C:\gfortran\clf\sizetest>sizetest
> 48
> made it here...
> 48

--

hatings...@gmail.com

unread,
Jan 7, 2009, 12:19:01 PM1/7/09
to
Richard,

I believe I see what you are saying, since the allocatable array
object holds the array descriptor such as shape, stride, size and not
just the memory address and the standard does not specify how a
compiler should implement the descriptors, this information is stored
differently depending on the compiler. So C would not understand how
to interpret the extra descriptors. If you use C_LOC(x%y) and y is a
allocatable component then it is no guarantee that the address it
returns is the start of the data section, and even if it were there is
no guarantee that the data is continuous in memory. It would be non-
standard anyway since each component of shall be a nonpointer and
nonallocatable to be interpretable. One would need not just to know
the "sizeof" the datatype but also be able to interpret the array
descriptor in order to extract the information correctly on the C side
of things. Even with James's first example the offset of each derive
type component (assuming more then one) would be hard to find even if
the data elements are continuous in memory (at least there does not
seem to be a portable way of obtaining the offset to me).

Reinhold Bader

unread,
Jan 7, 2009, 2:50:19 PM1/7/09
to
James Van Buskirk schrieb:

>
> So we can see that there are two standard flavors of SIZEOF, the
> one with TRANSFER dating back to f90 and the one with C_SIZEOF
> requiring f03.
>

C_SIZEOF needs Fortran 2008, actually.

Regards

James Van Buskirk

unread,
Jan 7, 2009, 3:02:19 PM1/7/09
to
"Reinhold Bader" <Ba...@lrz.de> wrote in message
news:gk311r$3jr$00$1...@news.t-online.com...

> James Van Buskirk schrieb:

Oops. Thank you for pointing this out.

Richard Maine

unread,
Jan 7, 2009, 3:11:58 PM1/7/09
to
<hatings...@gmail.com> wrote:

> I believe I see what you are saying,

Yes, I think so now.

> If you use C_LOC(x%y) and y is a
> allocatable component then it is no guarantee that the address it
> returns is the start of the data section,

I think that "ought" to be the address of the data rather than of the
descriptor, but I didn't actually go check the standard to make sure;
that just seems like it ought to be the case. But it doesn't help
because of the other issues, which I think you do now see.

Steven Correll

unread,
Jan 8, 2009, 10:37:21 AM1/8/09
to
On Jan 7, 1:11 pm, nos...@see.signature (Richard Maine) wrote:

> <hatingspam2...@gmail.com> wrote:
> > If you use C_LOC(x%y) and y is a
> > allocatable component then it is no guarantee that the address it
> > returns is the start of the data section,...[snip]

>
> I think that "ought" to be the address of the data rather than of the
> descriptor, but I didn't actually go check the standard to make sure;
> that just seems like it ought to be the case...[snip]

I believe the 2003 standard confirms your "ought". From 15.1.2.5, if
the argument of C_LOC is "X" and the result is called "CPTR":

"If X is an array data entity, the result is determined as if C_PTR
were a derived type
containing a scalar pointer component PX of the type and type
parameters of X and the
pointer assignment of CPTR%PX to the first element of X were executed"

(It seems a bit strange to say "scalar pointer component", which
implies a Fortran pointer in most places in the standard, when the
purpose is to generate a C pointer. I would have thought it better to
say that using C_LOC and C_F_POINTER in succession would generate a
Fortran pointer to the first element of X. But in any case, it says
without qualification that C_LOC shall point to the first element of
the array data, regardless of whether the array is allocatable.)

hatings...@gmail.com

unread,
Jan 8, 2009, 11:25:15 AM1/8/09
to

If X is a derived type with an allocatable component Y, would the
argument X%Y in C_LOC(X%Y) be considered interoperable? The derived
type itself would be noninteroperable, can you have interoperable
components of a noninteroperable derived type, that does not appear to
be the case. The standard assumes that X is interoperable ...
or a nonpolymorphic scalar...

Richard Maine

unread,
Jan 8, 2009, 12:22:31 PM1/8/09
to
<hatings...@gmail.com> wrote:

> If X is a derived type with an allocatable component Y, would the
> argument X%Y in C_LOC(X%Y) be considered interoperable? The derived
> type itself would be noninteroperable, can you have interoperable
> components of a noninteroperable derived type, that does not appear to
> be the case. The standard assumes that X is interoperable ...
> or a nonpolymorphic scalar...

Yes, you can have interoperable components of a non-interoperable
derived type. In fact, it is quite common. Consider something much
simpler than an allocatable component. Take a scalar integer component
of an interoperable kind. LIkewise, an element of a non-interoperable
array (such as an assumed shape dummy argument) may be interoperable.

If you look at the definitions, the "parent" object doesn't enter into
it. Recall that x%y is a variable (if x is a variable). All the
definitions of what it means for a variable to be interoperable apply to
x%y directly. None of those definitions make any reference to x.

George

unread,
Jan 10, 2009, 12:52:18 AM1/10/09
to
On Thu, 8 Jan 2009 09:22:31 -0800, Richard Maine wrote:

> <hatings...@gmail.com> wrote:
>
>> If X is a derived type with an allocatable component Y, would the
>> argument X%Y in C_LOC(X%Y) be considered interoperable? The derived
>> type itself would be noninteroperable, can you have interoperable
>> components of a noninteroperable derived type, that does not appear to
>> be the case. The standard assumes that X is interoperable ...
>> or a nonpolymorphic scalar...
>
> Yes, you can have interoperable components of a non-interoperable
> derived type. In fact, it is quite common. Consider something much
> simpler than an allocatable component. Take a scalar integer component
> of an interoperable kind. LIkewise, an element of a non-interoperable
> array (such as an assumed shape dummy argument) may be interoperable.
>
> If you look at the definitions, the "parent" object doesn't enter into
> it. Recall that x%y is a variable (if x is a variable). All the
> definitions of what it means for a variable to be interoperable apply to
> x%y directly. None of those definitions make any reference to x.

I'd like to see a code snippet.
--
George

The resolve of our great nation is being tested. But make no mistake, we
will show the world that we will pass the test.
George W. Bush

Picture of the Day http://apod.nasa.gov/apod/

0 new messages