[MPI3 Fortran] Derived-data, a new/late comment on Fortran WG5 ballot N1846

Rolf Rabenseifner rabenseifner at hlrs.de
Thu Apr 14 09:22:55 CDT 2011


Dear John, dear members of the WG5 and J3 Fortran committees,

I'm sorry that with this additional comment on problems
regarding derived types, I missed the deadline of the N1846 
ballot for the N1845 draft of the TR 29113 on extensions on 
Fortran-C interoperability.  

It looks like that there are two problems with derived types
and the Fortran-MPI-compatibility with a background in the
Fortran-C-interoperability.

Problem A: Sequence derived types in the MPI routine 
           interfaces, which are declared with BIND(C);
           this problem occurs with the new MPI handles 
           and MPI statuses.  

Problem B: Derived type, SEQUENCE derived type, and
           BIND(C) derived type as actual user buffers 
           for TYPE(*),DIMENSION(..) dummy arguments
           in BIND(C) MPI routine interfaces.

Problem C: Based on problem B we have the question
           whether the new TYPE(*),DIMENSION(..) dummy 
           arguments in BIND(C) MPI routine interfaces
           really allow all actual arguments that were
           possible with implicit interfaces or with
           explicit interfaces in combination with 
           pragmas like 
             !DEC$ ATTRIBUTES NO_ARG_CHECK :: buf
           and 
             !$PRAGMA IGNORE_TKR buf

At least for problems A and B, the solution may be "simple" 
by allowing SEQUENCE derived types as element of a 
BIND(C) derived type and in BIND(C) subroutine dummy arguments.
Why we need this is shown in very detail in the following 
description of Problems A and B.

A still open question is Problem C.


To Problem A:
------------- 

For better type-safety and compile-time argument-checking,
the MPI Forum wants to use named types for MPI handles
and MPI status.
In MPI-1.1 up to MPI-2.2, we use INTEGER and 
INTEGER, DIMENSION(MPI_STATUS_SIZE) for this.

With the new module mpi_f08 in MPI-3.0, we want to use
 
  MODULE mpi_f08 
    IMPLICIT NONE
    TYPE :: MPI_Comm
    SEQUENCE 
      INTEGER :: MPI_VAL 
    END TYPE MPI_Comm
  
    TYPE :: MPI_Status
    SEQUENCE 
      INTEGER :: MPI_SOURCE
      INTEGER :: MPI_TAG 
      INTEGER :: MPI_ERROR
      INTEGER :: MPI_intern_highsize
      INTEGER :: MPI_intern_lowsize
    END TYPE MPI_Status
  END MODULE mpi_f08 
 
Within existing user applications, it is important, that 
the new handles and status variables can be used everywhere, 
where the old-style INTEGER handles and INTEGER-array statuses 
are already used.   

This definition can be used in
 - user-defined arrays of handles or statuses
 - handles and statuses as part of a user-defined common block
 - handles and statuses as part of a user-defined derived type 
 - handles and statuses as part of a user-defined sequence 
   derived type 

In my attached the tests Bu1.f90, Bu2.f90 and Bu3.f90, 
this was checked by Reinhold Bader for many compilers.

If an application already uses C-Fortran interoperability,
it may be that such handles and statuses are also declared
with a BIND(C) derived type.
The test Bu4.f90 showed that this works with ifort and pgi,
but is rejected by gfortran, nagfor, xlf, crayftn, and pathscale.

In the tests Au1, Au2, Au3, Au4, the SEQUENCE attribute was
removed from the definition of MPI handles and statuses;
nearly all compiler reject nearly all use-cases.

In the tests Cu1, Cu2, Cu3, Cu4, the SEQUENCE was substituted
by BIND(C). This is rejected by all compilers for the 
case that a handle or status is part of a user-defined
sequence derived type (see Cu3).

Another problem is the implementation of the MPI routines.
We want to be able to use wrappers written in C, 
i.e., to use BIND(C) for the definition of MPI routines.
The test Bc1 calls an MPI routine that has a pure Fortran 
implementation, while Bc2 calls an MPI routine that is
implemented with BIND(C).

Bc1 of course works with all compilers, while
Bc2 is rejected by gfortran, nagfor, xlf and pathscale.
 
Same rejections occur if the handles are defined
without SEQUENCE (see Ac2).

Of course, in case C, handles are done with BIND(C),
all compiler accept the MPI routines (see Cc2),
but this does not really help, because the 
application use-case Cu3 was rejected by all compilers.

How can this problem be solved?
Sequence derived types are similar to common blocks
and as long as normal Fortran types (INTEGER, REAL)
are allowed with BIND(C), why is a sequence
of such types is not allowed with BIND(C)?

Which additions would be necessary to solve this problem 
within the TR 29113?

To Problem B:
------------- 

As an example, here an MPI interface
 
  SUBROUTINE MPI_xxx(buf,...) BIND(C)
    TYPE(*), DIMENSION(..) :: buf
  END

within the new MPI module
and the following user code

  TYPE :: user_xxx
    SEQUENCE
      REAL, DIMENSION(100) :: x, y, z
      INTEGER, DIMEMSION(20) :: a, b
  END TYPE user_xxx

  TYPE(user_xxx) :: strct(5)

  CALL MPI_xxx(strct, ...) 
 
When I understood correctly, then strct is handed over
through a dope vector with elem_len = sizeof(strct(1)).

Without any SEQUENCE or BIND(C) for user_xxx,
the compiler may optimize and modify the memory layout
of the structure during the execution of the application,
i.e., any address difference need not to be constant,
e.g., LOC(strct(5)%b(1)) - LOC(strct(1)%x(1))
need not to be the same during the whole execution and
within the application and the called MPI routine. 
Is this correct?

To achieve a well-defined memory layout, the user
has to use SEQUENCE or BIND(C) for user_xxx. 

Therefore in the past, the advice for MPI users was,
to use the SEQUENCE attribute.

Results from the compiler tests are:
All compiler allow the usage of SEQUENCE and BIND(C)
derived type as actual buffer arguments in implicit
interfaces of MPI routines, see cases 1 and 2
in the tests to problem B.
All compiler with a IGNORE_TKR directive allow
SEQUENCE and BIND(C) derived type as actual buffer 
arguments in an explicit interface defined with 
INTERFACE, see cases 4 and 5.
Normal derived types (that are neither SEQUENCE, nor
BIND(C), nor defined within a module) cannot be used
as such an actual buffer argument with the IBM
xlf compiler, see cases 3 and 6. 
Same results have been obtained with explicit interfaces
defined with CONTAINS, except for xlf, which does not
allow the IGNORE_TKR directive outside of 
INTERFACE declarations. 


Do I understand correctly, that with N1845 of TR 29113,
TYPE(*),DIMENSION(..) works only with
BIND(C) derived types, but 
 - not with normal derived types, and
 - not with sequence derived types?

Is there a possibility to extend the TR that
also sequence derived type can be handed over to
TYPE(*), DIMENSION(..) dummy arguments?  

Problem C:
----------

Do we have other actual arguments that could be used in
implicit interfaces or in explicit interfaces with
these special pragmas, and that are still forbidden
for TYPE(*),DIMENSION(..) dummy arguments?

Best regards
and my apologies that we detected the problem not earlier,
Rolf 

---------------------------------------------------------
Test and file names for Problem A:
---------------------------------- 

   Implementing new MPI handles and status with ... 
    A = Fortran derived type 
    B = Fortran sequence derived type 
    C = Fortran BIND(C) derived type 
  
   Usage of new MPI handles and status in the application within ...
    u1 = a user defined common block
    u2 = a user defined derived type
    u3 = a user defined sequence derived type
    u4 = a user defined BIND(C) derived type
  
   Call an MPI routine that is defined
    c1 = without BIND(C) 
    c2 = with BIND(C) 

Compiler: 
 
   Result are:
    R - rejected by the compiler
    i - compiles but issues an information or warning
    y - compiles 
 

Test -->          | A A A A  A A | B B B B  B B | C C C C  C C |
                  | u u u u  c c | u u u u  c c | u u u u  c c |
                  | 1 2 3 4  1 2 | 1 2 3 4  1 2 | 1 2 3 4  1 2 |
------------------+--------------+--------------+--------------+
ifort  6.1        | R y R y  y y | y y y y  y y | R y R y  y y |
ifort 11.1        | y y R y  y y | y y y y  y y | y y R y  y y |
ifort 12.0        | y y R y  y y | y y y y  y y | y y R y  y y |
------------------+--------------+--------------+--------------+
gfortran 4.6      | R y R R  y R | y y y R  y R | i i R i  i i |
nagfor 5.2        | R i R R  i R | y i i R  i R | y i R i  i i |
------------------+--------------+--------------+--------------+
xlf 13.1          | R y R R  y R | y y y R  y R | y y R y  y y |
crayftn 7.3       | R y R R  y y | y y y R  y y | y y R y  y y |
------------------+--------------+--------------+--------------+
pgi 11.3          | y y R y  y y | y y y y  y y | y y R y  y y |
pathscale 3.3b    | R i R R  i R | i i i R  i R | i i R i  i i |
------------------+--------------+--------------+--------------+

Notes: 
      "i" entries from the NAG compiler are due to defined but unused entities.
      "i" entries from the gfortran compiler are wrt INTEGER, ... potentially 
          being non-interoperable.
      "i" entries from the Pathscale compiler are (irrelevant) link-time messages.

Tar file:  
 - MPI3_bind-C_sequence_tests.tar.gz (attached)

-----------------------------------------------------------------
Test and file names for Problem B:
---------------------------------- 
 
Test and file names:

  derived_types_test_1_impl_integer.f90
  derived_types_test_2_impl_sequ_bc.f90
  derived_types_test_3_impl_derived.f90
  derived_types_test_4_expl_integer.f90
  derived_types_test_5_expl_sequ_bc.f90
  derived_types_test_6_expl_derived.f90
  derived_types_test_7_all.f90
  derived_types_test_1+2_impl_int+seq+bc.f90

  with
    impl = Implicitly defined MPI routine is called.
    expl = Two explicitly defined MPI routines are called
            - without BIND(C),
            - with BIND(C) in the subroutine declaration.
           The buf dummy argument is defined with a TKR ignore directive.

    integer = Actual argument is a derived type and
              it is passed through first (integer) element.
              Three different derived types are used:
               - normal,
               - with SEQUENCE attribute,
               - with BIND(C) attribute.
    sequ_bc = Actual argument is a derived type with
               - with SEQUENCE attribute,
               - with BIND(C) attribute.
    derived = Actual argument is a normal derived type.

  The last test "1+2" is a special test to show a compile-time
  error only detected by nagfor. This test compines the calls in
  ..._1_impl_integer.f90 and ..._2_impl_sequ_bc.f90.


Compiler results may be:

    R  - rejected by the compiler
    Rs - rejected by the compiler (routines and main separately compiled)
    i  - compiles but issues an information or warning and runs correctly
    y  - compiles and runs correctly
    ys - compiles and runs correctly (routines and main separately compiled)
    N  - compiles, then runs with run time failure


Test -->          |  ---impl---   ---expl---   all   impl
                  |  int seq drv  int seq drv      int+seq
                  |   1   2   3    4   5   6    7    1+2
------------------+---------------------------------------
ifort 11.1        |   y   y   y    y   y   y    y     y
ifort 12.0        |   y   y   y    y   y   y    y     y
------------------+---------------------------------------
gfortran 4.6      |   y   y   y    R   R   R    R     y
nagfor 5.2        |   ys  ys  ys   Rs  Rs  Rs   Rs    Rs
------------------+---------------------------------------
xlf 13.1          |   y   y   R    y   y   R    R     y
crayftn 7.3       |   i   i   i    y   y   y    i     i
------------------+---------------------------------------
pgi 11.3          |   y   y   y    y   y   y    y     y
pathscale 3.3b    |   i   i   i    y   y   y    i     i
------------------+---------------------------------------

Notes:
 - Compile-time information, warning and errors with the CALL statements

      gfortran + 1,all      : Rank mismatch warning (rank-1 vs scalar lines for all invocations)
      gfortran + 2,3,all    : Type mismatch warning
      gfortran + 4,all      : Rank mismatch error (rank-1 vs scalar lines for all invocations),
                                i.e., none of the TKR_IGNORE directives work
      gfortran + 5,6,all    : Type mismatch error,
                                i.e., none of the TKR_IGNORE directives work
      nagfor  + 4,all       : Rank mismatch error (rank-1 vs scalar lines for all invocations),
                                i.e., none of the TKR_IGNORE directives work
      nagfor  + 5,6,all     : Type mismatch error,
                                i.e., none of the TKR_IGNORE directives work
      nagfor  + 1+2, all    : Error: Inconsistency between several calls of implicitly defined routine:
                                "Inconsistent data type INTEGER (previously USER_BUFFER_NORMAL_TYPE)
                                for argument 3 in reference to FOO_IMPL",
                                i.e., a combination of the tests in 1 and 2 or 3 may fail.
      crayftn+1,2,3,all,1+2 : Rank mismatch diagnosed, but runs correctly
      xlf + 3,6, all        : Severe error:
                                "A derived-type object that appears as an actual argument in
                                an external procedure reference must be of a sequence type or
                                a type with the BIND(C) attribute, unless it is use-associated
                                or of a type that is use-associated or defined in the
                                specification part of a module.
      pathscale+1-3,all,1+2 : Warns about rank mismatch, but runs correctly.

 - Compile-time information, warning and errors with the declaration statement of MPI_foo...,
   i.e., when compiling the MPI library:

      gfortran + 4,5,6,all  : Warning with BIND(C) declarations:
                                INTEGER may not be interoperable with C, related
                                to line "SUBROUTINE MPI_foo_ex_c(c1,c2,buf,test1,test2) BIND(C)"
      nagfor + "routines"   : Additional information that BIND(C) is an "extension"
                                in line "SUBROUTINE MPI_foo_ex_c(c1,c2,buf,test1,test2) BIND(C)"

 - Other compile-time information, warning and errors:

      gfortran+1,2,4,5,all,1+2:Warning with BIND(C) declarations:
                                INTEGER may not be interoperable with C, related
                                to line "TYPE, BIND(C) :: user_buffer_bind_c_type"
      nagfor+1,2,4,5,all,1+2: Additional information that BIND(C) is an "extension"
                                in line "TYPE, BIND(C) :: user_buffer_bind_c_type"

 - Runtime errors were never detected, i.e.,
   in the cases with actual argument = buf%VAL1 (i.e., the first element of the derived type),
   all compilers used call by reference, i.e., the called implicit or explicit routines
   could correctly access also the second element of the derived type.

Tar file:  
 - MPI3_derived_types_test.tar.gz (attached)

Acknowledgments: 
 I want to thank Reinhold Bader (LRZ, Munich, Germany) who made all the compiler protocols.



-- 
Dr. Rolf Rabenseifner . . . . . . . . . .. email rabenseifner at hlrs.de
High Performance Computing Center (HLRS) . phone ++49(0)711/685-65530
University of Stuttgart . . . . . . . . .. fax ++49(0)711 / 685-65832
Head of Dpmt Parallel Computing . . . www.hlrs.de/people/rabenseifner
Nobelstr. 19, D-70550 Stuttgart, Germany . (Office: Allmandring 30)
-------------- next part --------------
A non-text attachment was scrubbed...
Name: MPI3_bind-C_sequence_tests.tar.gz
Type: application/x-compressed-tar
Size: 2333 bytes
Desc: not available
URL: <http://lists.mpi-forum.org/pipermail/mpiwg-fortran/attachments/20110414/b0a2ce7a/attachment-0002.bin>
-------------- next part --------------
A non-text attachment was scrubbed...
Name: MPI3_derived_types_test.tar.gz
Type: application/x-compressed-tar
Size: 13232 bytes
Desc: not available
URL: <http://lists.mpi-forum.org/pipermail/mpiwg-fortran/attachments/20110414/b0a2ce7a/attachment-0003.bin>


More information about the mpiwg-fortran mailing list