source: XMLIO_V2/dev/dev_rv/src/fortran/impi_interface.f90 @ 141

Last change on this file since 141 was 141, checked in by hozdoba, 13 years ago

Mise à jour depuis un autre dépôt

File size: 8.2 KB
Line 
1MODULE IMPI_INTERFACE
2   USE ISO_C_BINDING
3
4include "mpif.h"
5
6   INTEGER (kind = C_INT ), BIND(C, NAME = "mpi_success" )     :: xios_mpi_success     = MPI_SUCCESS
7   INTEGER (kind = C_INT ), BIND(C, NAME = "mpi_comm_world" )  :: xios_mpi_comm_world  = MPI_COMM_WORLD
8   INTEGER (kind = C_INT ), BIND(C, NAME = "mpi_char" )        :: xios_mpi_char        = MPI_CHARACTER
9   INTEGER (kind = C_INT ), BIND(C, NAME = "mpi_status_size" ) :: xios_mpi_status_size = MPI_STATUS_SIZE
10   INTEGER (kind = C_INT ), BIND(C, NAME = "mpi_any_tag" )     :: xios_mpi_any_tag     = MPI_ANY_TAG
11
12   CONTAINS
13
14   ! Initialiser MPI
15   SUBROUTINE xios_mpi_init(err) BIND(C, NAME ="mpi_init")
16      INTEGER  (kind = C_INT) :: err
17      CALL MPI_INIT(err)
18   END SUBROUTINE xios_mpi_init
19
20   ! Quitter MPI
21   SUBROUTINE xios_mpi_finalize(err) BIND(C, NAME ="mpi_finalize")
22      INTEGER  (kind = C_INT) :: err
23      CALL MPI_FINALIZE(err)
24   END SUBROUTINE xios_mpi_finalize
25
26   ! Quitter brutalement MPI
27   SUBROUTINE xios_mpi_abort(comm, errcode, err) BIND(C, NAME ="mpi_abort")
28      INTEGER  (kind = C_INT) :: comm, errcode, err
29      CALL MPI_ABORT(comm, errcode, err)
30   END SUBROUTINE xios_mpi_abort
31
32   ! Savoir si un processus à fait un MPI_INIT
33   SUBROUTINE xios_mpi_initialized(flag, err) BIND(C, NAME ="mpi_initialized")
34      LOGICAL (kind = C_BOOL) :: flag
35      INTEGER (kind = C_INT)  :: err
36      LOGICAL                 :: cflag
37      cflag = flag
38      CALL MPI_INITIALIZED(cflag, err)
39   END SUBROUTINE xios_mpi_initialized
40
41   ! Récupérer la chaine de caractÚres associée au code d'erreur err
42   SUBROUTINE xios_mpi_error_string(errcode, chaine, taille_chaine, err) &
43                                    BIND(C, NAME ="mpi_error_string")
44      INTEGER (kind = C_INT)                 :: errcode, taille_chaine, err
45      CHARACTER(kind = C_CHAR), DIMENSION(*) :: chaine
46      CHARACTER(len = taille_chaine)         :: cchaine
47      CALL MPI_ERROR_STRING(errcode, cchaine, taille_chaine, err)
48      chaine(taille_chaine) = cchaine
49   END SUBROUTINE xios_mpi_error_string
50
51   ! Envoyer un message à un processus
52   SUBROUTINE xios_mpi_send(buf, count, datatype, dest, tag, comm, err) &
53                            BIND(C, NAME ="mpi_send")
54      CHARACTER(kind = C_CHAR), DIMENSION(*) :: buf
55      INTEGER (kind = C_INT)                 :: dest, count, datatype, tag, comm, err
56      CALL MPI_SEND(buf, count, datatype, dest, tag, comm, err)
57   END SUBROUTINE xios_mpi_send
58
59   ! Recevoir un message d'un processus
60   SUBROUTINE xios_mpi_recv(buf, count, datatype, source, &
61                            tag, comm, status, err)       &
62                            BIND(C, NAME ="mpi_recv")
63      CHARACTER(kind = C_CHAR), DIMENSION(*)              :: buf
64      INTEGER (kind = C_INT)                              :: count, datatype, source, tag, comm, err
65      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
66      CALL MPI_RECV(buf, count, datatype, source, tag, comm, status, err)
67   END SUBROUTINE xios_mpi_recv
68
69   ! Envoyer et recevoir un message
70   SUBROUTINE xios_mpi_sendrecv(sendbuf, sendcount, sendtype, dest, sendtag, recvbuf, recvcount, &
71                                recvtype, source, recvtag, comm, status, err) &
72                                BIND(C, NAME ="mpi_sendrecv")
73      CHARACTER(kind = C_CHAR), DIMENSION(*) :: sendbuf, recvbuf
74      INTEGER (kind = C_INT)                 :: sendcount, sendtype, dest, sendtag, recvcount, &
75                                                recvtype, source, recvtag, comm, err
76      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
77      CALL MPI_SENDRECV(sendbuf, sendcount, sendtype, dest, sendtag, recvbuf, &
78                        recvcount, recvtype, source, recvtag, comm, status, err)
79   END SUBROUTINE xios_mpi_sendrecv
80
81   ! Compter le nombre d'éléments reçus
82   SUBROUTINE xios_mpi_get_count(status, datatype, count, err) BIND(C, NAME ="mpi_get_count")
83      INTEGER (kind = C_INT)                 :: datatype, count, err
84      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
85      CALL MPI_GET_COUNT(status, datatype, count, err)
86   END SUBROUTINE xios_mpi_get_count
87
88   ! Tester l'arrivée d'un message
89   SUBROUTINE xios_mpi_iprobe(source, tag, comm, flag, status, err) BIND(C, NAME ="mpi_iprobe")
90      INTEGER (kind = C_INT) :: source, tag, comm, err
91      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
92      LOGICAL (kind = C_BOOL) :: flag
93      CALL MPI_IPROBE(source, tag, comm, flag, status, err)
94   END SUBROUTINE xios_mpi_iprobe
95
96   ! Nombre de processus dans un intracommunicateur
97   SUBROUTINE xios_mpi_comm_size(comm, nbre, err) BIND(C, NAME ="mpi_comm_size")
98      INTEGER (kind = C_INT)  :: comm, nbre, err
99      CALL MPI_COMM_SIZE(comm, nbre, err)
100   END SUBROUTINE xios_mpi_comm_size
101
102   ! Rang d'un processus dans un intracommunicateur
103   SUBROUTINE xios_mpi_comm_rank(comm, rang, err) BIND(C, NAME ="mpi_comm_rank")
104      INTEGER (kind = C_INT)  :: comm, rang, err
105      CALL MPI_COMM_RANK(comm, rang, err )
106   END SUBROUTINE xios_mpi_comm_rank
107
108   ! Partage d'un communicateur
109   SUBROUTINE xios_mpi_comm_split(comm, couleur, cle, newcomm, err) BIND(C, NAME ="mpi_comm_split")
110      INTEGER (kind = C_INT)  :: comm, couleur, cle, newcomm, err
111      CALL MPI_COMM_SPLIT(comm, couleur, cle, newcomm, err)
112   END SUBROUTINE xios_mpi_comm_split
113
114   ! Commencer à envoyer un message
115   SUBROUTINE xios_mpi_issend(buf, count, datatype, dest, tag, comm, request, err) &
116                            BIND(C, NAME ="mpi_issend")
117      CHARACTER(kind = C_CHAR), DIMENSION(*) :: buf
118      INTEGER (kind = C_INT)                 :: count, datatype, tag, comm, request, err, dest
119      CALL MPI_ISSEND(buf, count, datatype, dest, tag, comm, request, err)
120   END SUBROUTINE xios_mpi_issend
121
122   ! Commencer à recevoir un message
123   SUBROUTINE xios_mpi_irecv(buf, count, datatype, source, &
124                            tag, comm, request, err)       &
125                            BIND(C, NAME ="mpi_irecv")
126      CHARACTER(kind = C_CHAR), DIMENSION(*)              :: buf
127      INTEGER (kind = C_INT)                              :: count, datatype, source, tag, &
128                                                             comm, request, err
129      CALL MPI_IRECV(buf, count, datatype, source, tag, comm, request, err)
130   END SUBROUTINE xios_mpi_irecv
131
132   ! Compléter une opération non bloquante
133   SUBROUTINE xios_mpi_wait(request, status, err) BIND(C, NAME ="mpi_wait")
134      INTEGER (kind = C_INT)                              :: request, err
135      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
136      CALL MPI_WAIT(request, status, err)
137   END SUBROUTINE xios_mpi_wait
138
139   ! Tester une opération non bloquante
140   SUBROUTINE xios_mpi_test(request, flag, status, err) BIND(C, NAME ="mpi_test")
141      INTEGER (kind = C_INT)                              :: request, err
142      INTEGER (kind = C_INT) , DIMENSION(mpi_status_size) :: status
143      LOGICAL (kind = C_BOOL)                             :: flag
144      LOGICAL                                             :: cflag
145      cflag = flag
146      CALL MPI_TEST(request, cflag, status, err)
147   END SUBROUTINE xios_mpi_test
148
149   ! Création d'un communicateur à partir d'un groupe
150   SUBROUTINE xios_mpi_comm_create(comm, group, newcomm, err) BIND(C, NAME ="mpi_comm_create")
151      INTEGER (kind = C_INT) :: comm, group, newcomm, err
152      CALL MPI_COMM_CREATE(comm, group, newcomm, err)
153   END SUBROUTINE xios_mpi_comm_create
154
155   ! Obtention d'une groupe à partir d'un communicateur
156   SUBROUTINE xios_mpi_comm_group(comm, group, err) BIND(C, NAME ="mpi_comm_group")
157      INTEGER (kind = C_INT) :: comm, group, err
158      CALL MPI_COMM_GROUP(comm, group, err)
159   END SUBROUTINE xios_mpi_comm_group
160
161   ! Création de sous-groupe
162   SUBROUTINE xios_mpi_group_incl(group, n, rank, newgroup, err) BIND(C, NAME ="mpi_group_incl")
163      INTEGER (kind = C_INT) :: group, n,  newgroup, err
164      INTEGER (kind = C_INT) , DIMENSION(*) :: rank
165      CALL MPI_GROUP_INCL(group, n, rank, newgroup, err)
166   END SUBROUTINE xios_mpi_group_incl
167
168   ! BarriÚre
169   SUBROUTINE xios_mpi_barrier (comm, err) BIND (C, NAME ="mpi_barrier")
170      INTEGER (kind = C_INT) :: comm, err
171      CALL MPI_BARRIER(comm, err)
172   END SUBROUTINE xios_mpi_barrier
173
174END MODULE IMPI_INTERFACE
Note: See TracBrowser for help on using the repository browser.