source: XMLIO_SERVER/trunk/src/IOSERVER/mod_ioclient.f90 @ 27

Last change on this file since 27 was 27, checked in by ymipsl, 15 years ago

Correction : utilisation d'OASIS par le server

File size: 1.2 KB
Line 
1MODULE mod_ioclient
2
3
4CONTAINS
5
6  SUBROUTINE init_ioclient(NEW_COMM)
7  USE mod_ioclient_para
8  USE mod_mpi_buffer_client
9  USE mod_wait
10  USE mod_ioserver_namelist
11  USE mod_event_client
12  USE iomanager
13  IMPLICIT NONE
14    INTEGER, INTENT(INOUT),OPTIONAL :: NEW_COMM
15
16    INTEGER :: Comm
17    INTEGER :: nb_server
18    INTEGER :: rank
19    INTEGER :: ierr
20    LOGICAL :: init
21    INCLUDE 'mpif.h'
22 
23    CALL read_namelist
24
25    IF (using_server) THEN
26      CALL Init_parallel
27      CALL Init_mpi_buffer
28      CALL Init_wait
29      IF (PRESENT(NEW_COMM)) THEN
30        NEW_COMM=intracomm
31      ENDIF
32    ELSE
33      CALL MPI_INITIALIZED(init,ierr)
34      IF (init) THEN
35        IF (.NOT. PRESENT(NEW_COMM)) THEN
36           Comm=MPI_COMM_WORLD
37        ELSE
38          Comm=New_Comm
39        ENDIF
40      ELSE
41        CALL MPI_INIT(ierr)
42        Comm=MPI_COMM_WORLD
43       
44        IF (PRESENT(NEW_COMM)) THEN
45          New_Comm=MPI_COMM_WORLD
46        ENDIF
47      ENDIF 
48      CALL MPI_COMM_SIZE(Comm,nb_server,ierr)     
49      CALL MPI_COMM_RANK(Comm,rank,ierr)
50      CALL iom__init(1,nb_server,rank)
51      CALL iom__set_current_rank(1)
52    ENDIF
53   
54  END SUBROUTINE init_ioclient
55
56END MODULE mod_ioclient
Note: See TracBrowser for help on using the repository browser.