source: LMDZ5/trunk/libf/dyn3dpar/parallel_lmdz.F90 @ 1965

Last change on this file since 1965 was 1965, checked in by acaubel, 10 years ago

AC : Modified to run with Oasis-MCT as coupler in IPSLCM6 coupled configuration

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 15.2 KB
Line 
1!
2! $Id: parallel.F90 1810 2013-07-24 08:06:39Z emillour $
3!
4  MODULE parallel_lmdz
5  USE mod_const_mpi
6#ifdef CPP_IOIPSL
7      use IOIPSL, only: getin
8#else
9! if not using IOIPSL, we still need to use (a local version of) getin
10      use ioipsl_getincom, only: getin
11#endif   
12   
13    LOGICAL,SAVE :: using_mpi=.TRUE.
14    LOGICAL,SAVE :: using_omp
15   
16    integer, save :: mpi_size
17    integer, save :: mpi_rank
18    integer, save :: jj_begin
19    integer, save :: jj_end
20    integer, save :: jj_nb
21    integer, save :: ij_begin
22    integer, save :: ij_end
23    logical, save :: pole_nord
24    logical, save :: pole_sud
25   
26    integer, allocatable, save, dimension(:) :: jj_begin_para
27    integer, allocatable, save, dimension(:) :: jj_end_para
28    integer, allocatable, save, dimension(:) :: jj_nb_para
29    integer, save :: OMP_CHUNK
30    integer, save :: omp_rank
31    integer, save :: omp_size 
32!$OMP THREADPRIVATE(omp_rank)
33
34 contains
35 
36    subroutine init_parallel
37    USE vampir
38    implicit none
39#ifdef CPP_MPI
40      include 'mpif.h'
41#endif
42#include "dimensions.h"
43#include "paramet.h"
44#include "iniprint.h"
45
46      integer :: ierr
47      integer :: i,j
48      integer :: type_size
49      integer, dimension(3) :: blocklen,type
50      integer :: comp_id
51      character(len=4)  :: num
52      character(len=20) :: filename
53 
54#ifdef CPP_OMP   
55      INTEGER :: OMP_GET_NUM_THREADS
56      EXTERNAL OMP_GET_NUM_THREADS
57      INTEGER :: OMP_GET_THREAD_NUM
58      EXTERNAL OMP_GET_THREAD_NUM
59#endif 
60
61#ifdef CPP_MPI
62       using_mpi=.TRUE.
63#else
64       using_mpi=.FALSE.
65#endif
66     
67
68#ifdef CPP_OMP
69       using_OMP=.TRUE.
70#else
71       using_OMP=.FALSE.
72#endif
73     
74      call InitVampir
75     
76      IF (using_mpi) THEN
77#ifdef CPP_MPI
78        call MPI_COMM_SIZE(COMM_LMDZ,mpi_size,ierr)
79        call MPI_COMM_RANK(COMM_LMDZ,mpi_rank,ierr)
80#endif
81      ELSE
82        mpi_size=1
83        mpi_rank=0
84      ENDIF
85
86
87! Open text output file with mpi_rank in suffix of file name
88      IF (lunout /= 5 .and. lunout /= 6) THEN
89         WRITE(num,'(I4.4)') mpi_rank
90         filename='lmdz.out_'//num
91         IF (mpi_rank .NE. 0) THEN
92            OPEN(UNIT=lunout,FILE=TRIM(filename),ACTION='write', &
93               STATUS='unknown',FORM='formatted',IOSTAT=ierr)
94         ENDIF
95      ENDIF
96
97     
98      allocate(jj_begin_para(0:mpi_size-1))
99      allocate(jj_end_para(0:mpi_size-1))
100      allocate(jj_nb_para(0:mpi_size-1))
101     
102      do i=0,mpi_size-1
103        jj_nb_para(i)=(jjm+1)/mpi_size
104        if ( i < MOD((jjm+1),mpi_size) ) jj_nb_para(i)=jj_nb_para(i)+1
105       
106        if (jj_nb_para(i) <= 2 ) then
107         
108         write(lunout,*)"Arret : le nombre de bande de lattitude par process est trop faible (<2)."
109         write(lunout,*)" ---> diminuez le nombre de CPU ou augmentez la taille en lattitude"
110         
111#ifdef CPP_MPI
112          IF (using_mpi) call MPI_ABORT(COMM_LMDZ,-1, ierr)
113#endif         
114        endif
115       
116      enddo
117     
118!      jj_nb_para(0)=11
119!      jj_nb_para(1)=25
120!      jj_nb_para(2)=25
121!      jj_nb_para(3)=12     
122
123      j=1
124     
125      do i=0,mpi_size-1
126       
127        jj_begin_para(i)=j
128        jj_end_para(i)=j+jj_Nb_para(i)-1
129        j=j+jj_Nb_para(i)
130     
131      enddo
132     
133      jj_begin = jj_begin_para(mpi_rank)
134      jj_end   = jj_end_para(mpi_rank)
135      jj_nb    = jj_nb_para(mpi_rank)
136     
137      ij_begin=(jj_begin-1)*iip1+1
138      ij_end=jj_end*iip1
139     
140      if (mpi_rank.eq.0) then
141        pole_nord=.TRUE.
142      else
143        pole_nord=.FALSE.
144      endif
145     
146      if (mpi_rank.eq.mpi_size-1) then
147        pole_sud=.TRUE.
148      else
149        pole_sud=.FALSE.
150      endif
151       
152      write(lunout,*)"init_parallel: jj_begin",jj_begin
153      write(lunout,*)"init_parallel: jj_end",jj_end
154      write(lunout,*)"init_parallel: ij_begin",ij_begin
155      write(lunout,*)"init_parallel: ij_end",ij_end
156
157!$OMP PARALLEL
158
159#ifdef CPP_OMP
160!$OMP MASTER
161        omp_size=OMP_GET_NUM_THREADS()
162!$OMP END MASTER
163!$OMP BARRIER
164        omp_rank=OMP_GET_THREAD_NUM()   
165
166!Config  Key  = omp_chunk
167!Config  Desc = taille des blocs openmp
168!Config  Def  = 1
169!Config  Help = defini la taille des packets d'it�ration openmp
170!Config         distribue a chaque tache lors de l'entree dans une
171!Config         boucle parallelisee
172
173!$OMP MASTER
174      omp_chunk=(llm+1)/omp_size
175      IF (MOD(llm+1,omp_size)/=0) omp_chunk=omp_chunk+1
176      CALL getin('omp_chunk',omp_chunk)
177!$OMP END MASTER
178!$OMP BARRIER       
179#else   
180        omp_size=1
181        omp_rank=0
182#endif
183!$OMP END PARALLEL         
184   
185    end subroutine init_parallel
186
187   
188    subroutine SetDistrib(jj_Nb_New)
189    implicit none
190
191#include "dimensions.h"
192#include "paramet.h"
193
194      INTEGER,dimension(0:MPI_Size-1) :: jj_Nb_New
195      INTEGER :: i 
196 
197      jj_Nb_Para=jj_Nb_New
198     
199      jj_begin_para(0)=1
200      jj_end_para(0)=jj_Nb_Para(0)
201     
202      do i=1,mpi_size-1
203       
204        jj_begin_para(i)=jj_end_para(i-1)+1
205        jj_end_para(i)=jj_begin_para(i)+jj_Nb_para(i)-1
206     
207      enddo
208     
209      jj_begin = jj_begin_para(mpi_rank)
210      jj_end   = jj_end_para(mpi_rank)
211      jj_nb    = jj_nb_para(mpi_rank)
212     
213      ij_begin=(jj_begin-1)*iip1+1
214      ij_end=jj_end*iip1
215
216    end subroutine SetDistrib
217
218
219
220   
221    subroutine Finalize_parallel
222#ifdef CPP_XIOS
223    ! ug Pour les sorties XIOS
224        USE wxios
225#endif
226#ifdef CPP_COUPLE
227! Use of Oasis-MCT coupler
228#if defined CPP_OMCT
229    use mod_prism
230#else
231    use mod_prism_proto
232#endif
233! Ehouarn: surface_data module is in 'phylmd' ...
234      use surface_data, only : type_ocean
235      implicit none
236#else
237      implicit none
238! without the surface_data module, we declare (and set) a dummy 'type_ocean'
239      character(len=6),parameter :: type_ocean="dummy"
240#endif
241! #endif of #ifdef CPP_EARTH
242
243      include "dimensions.h"
244      include "paramet.h"
245#ifdef CPP_MPI
246      include 'mpif.h'
247#endif     
248
249      integer :: ierr
250      integer :: i
251
252      if (allocated(jj_begin_para)) deallocate(jj_begin_para)
253      if (allocated(jj_end_para))   deallocate(jj_end_para)
254      if (allocated(jj_nb_para))    deallocate(jj_nb_para)
255
256      if (type_ocean == 'couple') then
257#ifdef CPP_COUPLE
258         call prism_terminate_proto(ierr)
259         IF (ierr .ne. PRISM_Ok) THEN
260            call abort_gcm('Finalize_parallel',' Probleme dans prism_terminate_proto ',1)
261         endif
262#endif
263      else
264#ifdef CPP_XIOS
265    !Fermeture propre de XIOS
266      CALL wxios_close()
267#endif
268#ifdef CPP_MPI
269         IF (using_mpi) call MPI_FINALIZE(ierr)
270#endif
271      end if
272     
273    end subroutine Finalize_parallel
274       
275    subroutine Pack_Data(Field,ij,ll,row,Buffer)
276    implicit none
277
278#include "dimensions.h"
279#include "paramet.h"
280
281      integer, intent(in) :: ij,ll,row
282      real,dimension(ij,ll),intent(in) ::Field
283      real,dimension(ll*iip1*row), intent(out) :: Buffer
284           
285      integer :: Pos
286      integer :: i,l
287     
288      Pos=0
289      do l=1,ll
290        do i=1,row*iip1
291          Pos=Pos+1
292          Buffer(Pos)=Field(i,l)
293        enddo
294      enddo
295     
296    end subroutine Pack_data
297     
298    subroutine Unpack_Data(Field,ij,ll,row,Buffer)
299    implicit none
300
301#include "dimensions.h"
302#include "paramet.h"
303
304      integer, intent(in) :: ij,ll,row
305      real,dimension(ij,ll),intent(out) ::Field
306      real,dimension(ll*iip1*row), intent(in) :: Buffer
307           
308      integer :: Pos
309      integer :: i,l
310     
311      Pos=0
312     
313      do l=1,ll
314        do i=1,row*iip1
315          Pos=Pos+1
316          Field(i,l)=Buffer(Pos)
317        enddo
318      enddo
319     
320    end subroutine UnPack_data
321
322   
323    SUBROUTINE barrier
324    IMPLICIT NONE
325#ifdef CPP_MPI
326    INCLUDE 'mpif.h'
327#endif
328    INTEGER :: ierr
329   
330!$OMP CRITICAL (MPI)     
331#ifdef CPP_MPI
332      IF (using_mpi) CALL MPI_Barrier(COMM_LMDZ,ierr)
333#endif
334!$OMP END CRITICAL (MPI)
335   
336    END SUBROUTINE barrier
337       
338     
339    subroutine exchange_hallo(Field,ij,ll,up,down)
340    USE Vampir
341    implicit none
342#include "dimensions.h"
343#include "paramet.h"   
344#ifdef CPP_MPI
345    include 'mpif.h'
346#endif   
347      INTEGER :: ij,ll
348      REAL, dimension(ij,ll) :: Field
349      INTEGER :: up,down
350     
351      INTEGER :: ierr
352      LOGICAL :: SendUp,SendDown
353      LOGICAL :: RecvUp,RecvDown
354      INTEGER, DIMENSION(4) :: Request
355#ifdef CPP_MPI
356      INTEGER, DIMENSION(MPI_STATUS_SIZE,4) :: Status
357#else
358      INTEGER, DIMENSION(1,4) :: Status
359#endif
360      INTEGER :: NbRequest
361      REAL, dimension(:),allocatable :: Buffer_Send_up,Buffer_Send_down
362      REAL, dimension(:),allocatable :: Buffer_Recv_up,Buffer_Recv_down
363      INTEGER :: Buffer_size     
364
365      IF (using_mpi) THEN
366
367        CALL barrier
368     
369        call VTb(VThallo)
370     
371        SendUp=.TRUE.
372        SendDown=.TRUE.
373        RecvUp=.TRUE.
374        RecvDown=.TRUE.
375         
376        IF (pole_nord) THEN
377          SendUp=.FALSE.
378          RecvUp=.FALSE.
379        ENDIF
380   
381        IF (pole_sud) THEN
382          SendDown=.FALSE.
383          RecvDown=.FALSE.
384        ENDIF
385       
386        if (up.eq.0) then
387          SendDown=.FALSE.
388          RecvUp=.FALSE.
389        endif
390     
391        if (down.eq.0) then
392          SendUp=.FALSE.
393          RecvDown=.FALSE.
394        endif
395     
396        NbRequest=0
397 
398        IF (SendUp) THEN
399          NbRequest=NbRequest+1
400          buffer_size=down*iip1*ll
401          allocate(Buffer_Send_up(Buffer_size))
402          call PACK_Data(Field(ij_begin,1),ij,ll,down,Buffer_Send_up)
403!$OMP CRITICAL (MPI)
404#ifdef CPP_MPI
405          call MPI_ISSEND(Buffer_send_up,Buffer_Size,MPI_REAL8,MPI_Rank-1,1,     &
406                          COMM_LMDZ,Request(NbRequest),ierr)
407#endif
408!$OMP END CRITICAL (MPI)
409        ENDIF
410 
411        IF (SendDown) THEN
412          NbRequest=NbRequest+1
413           
414          buffer_size=up*iip1*ll
415          allocate(Buffer_Send_down(Buffer_size))
416          call PACK_Data(Field(ij_end+1-up*iip1,1),ij,ll,up,Buffer_send_down)
417       
418!$OMP CRITICAL (MPI)
419#ifdef CPP_MPI
420          call MPI_ISSEND(Buffer_send_down,Buffer_Size,MPI_REAL8,MPI_Rank+1,1,     &
421                          COMM_LMDZ,Request(NbRequest),ierr)
422#endif
423!$OMP END CRITICAL (MPI)
424        ENDIF
425   
426 
427        IF (RecvUp) THEN
428          NbRequest=NbRequest+1
429          buffer_size=up*iip1*ll
430          allocate(Buffer_recv_up(Buffer_size))
431             
432!$OMP CRITICAL (MPI)
433#ifdef CPP_MPI
434          call MPI_IRECV(Buffer_recv_up,Buffer_size,MPI_REAL8,MPI_Rank-1,1,  &
435                          COMM_LMDZ,Request(NbRequest),ierr)
436#endif
437!$OMP END CRITICAL (MPI)
438     
439       
440        ENDIF
441 
442        IF (RecvDown) THEN
443          NbRequest=NbRequest+1
444          buffer_size=down*iip1*ll
445          allocate(Buffer_recv_down(Buffer_size))
446       
447!$OMP CRITICAL (MPI)
448#ifdef CPP_MPI
449          call MPI_IRECV(Buffer_recv_down,Buffer_size,MPI_REAL8,MPI_Rank+1,1,     &
450                          COMM_LMDZ,Request(NbRequest),ierr)
451#endif
452!$OMP END CRITICAL (MPI)
453       
454        ENDIF
455 
456#ifdef CPP_MPI
457        if (NbRequest > 0) call MPI_WAITALL(NbRequest,Request,Status,ierr)
458#endif
459        IF (RecvUp)  call Unpack_Data(Field(ij_begin-up*iip1,1),ij,ll,up,Buffer_Recv_up)
460        IF (RecvDown) call Unpack_Data(Field(ij_end+1,1),ij,ll,down,Buffer_Recv_down) 
461
462        call VTe(VThallo)
463        call barrier
464     
465      ENDIF  ! using_mpi
466     
467      RETURN
468     
469    end subroutine exchange_Hallo
470   
471
472    subroutine Gather_Field(Field,ij,ll,rank)
473    implicit none
474#include "dimensions.h"
475#include "paramet.h"
476#include "iniprint.h"
477#ifdef CPP_MPI
478    include 'mpif.h'
479#endif   
480      INTEGER :: ij,ll,rank
481      REAL, dimension(ij,ll) :: Field
482      REAL, dimension(:),allocatable :: Buffer_send   
483      REAL, dimension(:),allocatable :: Buffer_Recv
484      INTEGER, dimension(0:MPI_Size-1) :: Recv_count, displ
485      INTEGER :: ierr
486      INTEGER ::i
487     
488      IF (using_mpi) THEN
489
490        if (ij==ip1jmp1) then
491           allocate(Buffer_send(iip1*ll*(jj_end-jj_begin+1)))
492           call Pack_Data(Field(ij_begin,1),ij,ll,jj_end-jj_begin+1,Buffer_send)
493        else if (ij==ip1jm) then
494           allocate(Buffer_send(iip1*ll*(min(jj_end,jjm)-jj_begin+1)))
495           call Pack_Data(Field(ij_begin,1),ij,ll,min(jj_end,jjm)-jj_begin+1,Buffer_send)
496        else
497           write(lunout,*)ij 
498        stop 'erreur dans Gather_Field'
499        endif
500       
501        if (MPI_Rank==rank) then
502          allocate(Buffer_Recv(ij*ll))
503
504!CDIR NOVECTOR
505          do i=0,MPI_Size-1
506             
507            if (ij==ip1jmp1) then
508              Recv_count(i)=(jj_end_para(i)-jj_begin_para(i)+1)*ll*iip1
509            else if (ij==ip1jm) then
510              Recv_count(i)=(min(jj_end_para(i),jjm)-jj_begin_para(i)+1)*ll*iip1
511            else
512              stop 'erreur dans Gather_Field'
513            endif
514                   
515            if (i==0) then
516              displ(i)=0
517            else
518              displ(i)=displ(i-1)+Recv_count(i-1)
519            endif
520           
521          enddo
522         
523        else
524          ! Ehouarn: When in debug mode, ifort complains (for call MPI_GATHERV
525          !          below) about Buffer_Recv() being not allocated.
526          !          So make a dummy allocation.
527          allocate(Buffer_Recv(1))
528        endif ! of if (MPI_Rank==rank)
529 
530!$OMP CRITICAL (MPI)
531#ifdef CPP_MPI
532        call MPI_GATHERV(Buffer_send,(min(ij_end,ij)-ij_begin+1)*ll,MPI_REAL8,   &
533                          Buffer_Recv,Recv_count,displ,MPI_REAL8,rank,COMM_LMDZ,ierr)
534#endif
535!$OMP END CRITICAL (MPI)
536     
537        if (MPI_Rank==rank) then                 
538     
539          if (ij==ip1jmp1) then
540            do i=0,MPI_Size-1
541              call Unpack_Data(Field((jj_begin_para(i)-1)*iip1+1,1),ij,ll,                 &
542                               jj_end_para(i)-jj_begin_para(i)+1,Buffer_Recv(displ(i)+1))
543            enddo
544          else if (ij==ip1jm) then
545            do i=0,MPI_Size-1
546               call Unpack_Data(Field((jj_begin_para(i)-1)*iip1+1,1),ij,ll,                       &
547                               min(jj_end_para(i),jjm)-jj_begin_para(i)+1,Buffer_Recv(displ(i)+1))
548            enddo
549          endif
550        endif
551      ENDIF ! using_mpi
552     
553    end subroutine Gather_Field
554
555
556    subroutine AllGather_Field(Field,ij,ll)
557    implicit none
558#include "dimensions.h"
559#include "paramet.h"   
560#ifdef CPP_MPI
561    include 'mpif.h'
562#endif   
563      INTEGER :: ij,ll
564      REAL, dimension(ij,ll) :: Field
565      INTEGER :: ierr
566     
567      IF (using_mpi) THEN
568        call Gather_Field(Field,ij,ll,0)
569!$OMP CRITICAL (MPI)
570#ifdef CPP_MPI
571      call MPI_BCAST(Field,ij*ll,MPI_REAL8,0,COMM_LMDZ,ierr)
572#endif
573!$OMP END CRITICAL (MPI)
574      ENDIF
575     
576    end subroutine AllGather_Field
577   
578   subroutine Broadcast_Field(Field,ij,ll,rank)
579    implicit none
580#include "dimensions.h"
581#include "paramet.h"   
582#ifdef CPP_MPI
583    include 'mpif.h'
584#endif   
585      INTEGER :: ij,ll
586      REAL, dimension(ij,ll) :: Field
587      INTEGER :: rank
588      INTEGER :: ierr
589     
590      IF (using_mpi) THEN
591     
592!$OMP CRITICAL (MPI)
593#ifdef CPP_MPI
594      call MPI_BCAST(Field,ij*ll,MPI_REAL8,rank,COMM_LMDZ,ierr)
595#endif
596!$OMP END CRITICAL (MPI)
597     
598      ENDIF
599    end subroutine Broadcast_Field
600       
601   
602!  Subroutine verif_hallo(Field,ij,ll,up,down)
603!    implicit none
604!#include "dimensions.h"
605!#include "paramet.h"   
606!    include 'mpif.h'
607!   
608!      INTEGER :: ij,ll
609!      REAL, dimension(ij,ll) :: Field
610!      INTEGER :: up,down
611!     
612!      REAL,dimension(ij,ll): NewField
613!     
614!      NewField=0
615!     
616!      ijb=ij_begin
617!      ije=ij_end
618!      if (pole_nord)
619!      NewField(ij_be       
620
621  end MODULE parallel_lmdz
Note: See TracBrowser for help on using the repository browser.