[MPI3 Fortran] MPI_SIZEOF question

Bill Long longb at cray.com
Mon May 23 14:39:45 CDT 2011



On 5/23/11 12:44 PM, Rolf Rabenseifner wrote:
>
> A) If we are doing BIND(C), I defined for MPI-3.0:
>
> INTERFACE
>   SUBROUTINE MPI_Sizeof(x, size, ierror) BIND(C)
>    IMPLICIT NONE
>    TYPE(*) :: x
>    INTEGER, INTENT(OUT) :: size
>    INTEGER, OPTIONAL, INTENT(OUT) :: ierror
>   END SUBROUTINE
> END INTERFACE
>
> This seems to be ***bad*** because TYPE(*) is not enough to
> get the dope vector

Correct. No dope vector here - just an address. Not useful in this case.


> TR 29113, 5.2.2, CFI_cdesc_t,
> especially its structure element
>
>    size_t elem_len; If the object corresponds to a Fortran
>       CHARACTER object, the value equals the length of
>       the CHARACTER object times the sizeof() of a scalar
>       of the character type; otherwise, the value equals
>       the sizeof() of an element of the object.
>
> We should do
>
>    TYPE(*), DIMENSION(..) :: x
>

Better.  dimension(..) will result in  a (point to the) dope vector 
being passed.

> which extends the current definition (in a backward compatible way).
>
> Then size = elem_len of the dope vector.
>
> Correct?

Yes, assuming the caller knows the type.

If you want the particular capitalization shown, you should make the 
first line of the routine

   subroutine MPI_Sizeof (x, size, ierror) BIND(C, name="MPI_Sizeof")

Without the name= specifier, the external name will be mpi_sizeof (all 
lower case).

This option seems like the best one - Fortran interface with C 
implementation. I assume this is not a performance sensitive routine, 
since there is overhead involved in creating the dope vector.

>
> B) If an implementation choose Fortran binding:
>
> B1) Does (without assumed-rank)
>
>   SUBROUTINE MPI_Sizeof(x, size, ierror)
>    IMPLICIT NONE
>    TYPE(*) :: x
>    INTEGER, INTENT(OUT) :: size
>    INTEGER, OPTIONAL, INTENT(OUT) :: ierror
>    size = SIZEOF(x)
>   END SUBROUTINE
>
> work?

No. SIZEOF is not a Fortran intrinsic, and there is no interface visible 
that indicates SIZEOF takes a type(*) argument.

There is a STORAGE_SIZE intrinsic that provides similar functionality, 
but it is not in the list of intrinsics that allow a type(*) argument.

>
> B2) Does (with assumed-rank)
>
>   SUBROUTINE MPI_Sizeof(x, size, ierror)
>    IMPLICIT NONE
>    TYPE(*), DIMENSION(..) :: x
>    INTEGER, INTENT(OUT) :: size
>    INTEGER, OPTIONAL, INTENT(OUT) :: ierror
>    size = SIZEOF(x)
>   END SUBROUTINE
>
> work, or how can it be programmed?

This suffers from the same problem as the previous example, since it 
fails the restrictions on what can be done with a type(*) variable.

An assumed-rank variable (dimension(..)) is allowed as an argument to 
STORAGE_SIZE, so it could be used in combination with explicit type 
arguments to greatly reduce the number of specifics in a generic 
interface.  Still would need interfaces for (typically) 4 (integer) * 4 
(logical) * 2 (real) * 2 (complex) * 1 (character) = 64 types.  Compared 
to the C implementation, this seems clumsy.

Cheers,
Bill


>
> Best regards
> Rolf
>
>
> ----- Original Message -----
>> From: "Bill Long"<longb at cray.com>
>> To: mpi3-fortran at lists.mpi-forum.org
>> Sent: Monday, May 23, 2011 4:47:26 PM
>> Subject: Re: [MPI3 Fortran] MPI_SIZEOF question
>>
>> The difficulty in writing things like this in Fortran is why the
>> standard provides intrinsics. In this case, see STORAGE_SIZE, which
>> returns the size of an array element of the type of the argument in
>> bits. Dividing by 8 and multiplying by the array size (if the argument
>> is not a scalar) should be simple enough for the user.
>>
>> On 5/23/11 8:30 AM, Jeff Squyres wrote:
>>> I'm re-working Open MPI's Fortran implementation with Craig.
>>>
>>> The MPI_SIZEOF function is supposed to return the size of any
>>> Fortran intrinsic data type. MPI-2.2 16.2.5 p494:31-44 says:
>>>
>>> -----
>>> The following functions allow a user to obtain a size-specific MPI
>>> datatype for any intrinsic Fortran type.
>>>
>>> MPI_SIZEOF(x, size)
>>> IN x a Fortran variable of numeric intrinsic type (choice)
>>> OUT size size of machine representation of that type (integer)
>>>
>>
>> This one is very close to STORAGE_SIZE. Just divide by 8.
>>
>>> MPI_SIZEOF(X, SIZE, IERROR)
>>> <type>  X
>>> INTEGER SIZE, IERROR
>>>
>>
>> This one would require also multiplying by the size of an array
>> argument. I assume the IERROR is there only to provide a distinction
>> for the generic interface. It is hard to imagine an actual run-time
>> error with a routine like this.
>>
>> Ultimately, I'd be inclined to just scrap the routine as redundant.
>>
>> Cheers,
>> Bill
>>
>>
>>> This function returns the size in bytes of the machine
>>> representation of the given variable. It is a generic Fortran
>>> routine and has a Fortran binding only.
>>> -----
>>>
>>> Is there any way of implementing that other than an interface with
>>> an overloaded subroutine for every single intrinsic type (including
>>> dimension)?
>>>
>>
>> --
>> Bill Long longb at cray.com
>> Fortran Technical Support&  voice: 651-605-9024
>> Bioinformatics Software Development fax: 651-605-9142
>> Cray Inc./Cray Plaza, Suite 210/380 Jackson St./St. Paul, MN 55101
>>
>>
>> _______________________________________________
>> mpi3-fortran mailing list
>> mpi3-fortran at lists.mpi-forum.org
>> http://lists.mpi-forum.org/mailman/listinfo.cgi/mpi3-fortran
>

-- 
Bill Long                                           longb at cray.com
Fortran Technical Support    &                 voice: 651-605-9024
Bioinformatics Software Development            fax:   651-605-9142
Cray Inc./Cray Plaza, Suite 210/380 Jackson St./St. Paul, MN 55101





More information about the mpiwg-fortran mailing list