source: branches/jerome/src_flexwrf_v3.1/sendint2_mpi.f90 @ 16

Last change on this file since 16 was 16, checked in by jebri, 11 years ago

sources for flexwrf v3.1

File size: 3.8 KB
Line 
1!***********************************************************************
2!* Copyright 2012,2013                                                *
3!* Jerome Brioude, Delia Arnold, Andreas Stohl, Wayne Angevine,       *
4!* John Burkhart, Massimo Cassiani, Adam Dingwell, Richard C Easter, Sabine Eckhardt,*
5!* Stephanie Evan, Jerome D Fast, Don Morton, Ignacio Pisso,          *
6!* Petra Seibert, Gerard Wotawa, Caroline Forster, Harald Sodemann,   *
7!*                                                                     *
8!* This file is part of FLEXPART WRF                                   *
9!*                                                                     *
10!* FLEXPART is free software: you can redistribute it and/or modify    *
11!* it under the terms of the GNU General Public License as published by*
12!* the Free Software Foundation, either version 3 of the License, or   *
13!* (at your option) any later version.                                 *
14!*                                                                     *
15!* FLEXPART is distributed in the hope that it will be useful,         *
16!* but WITHOUT ANY WARRANTY; without even the implied warranty of      *
17!* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the       *
18!* GNU General Public License for more details.                        *
19!*                                                                     *
20!* You should have received a copy of the GNU General Public License   *
21!* along with FLEXPART.  If not, see <http://www.gnu.org/licenses/>.   *
22!***********************************************************************
23
24  !   routine used to send integer*2 vectors by MPI
25  !    Author: J. Brioude                                                      *
26  !    March 2012                                                           *
27         subroutine sendint2_mpi(tag,numpart2,chunksize,direc)
28
29      use mpi_mod
30      use com_mod
31
32          implicit none
33      include 'mpif.h'
34
35!      character :: varname*20
36       integer :: chunksize,numpart2,jj1
37!      integer(kind=2) :: dummyi(numpart2),
38!      integer(kind=2) :: dummyi22(numpart2)
39       integer :: myid,ierr,ntasks,ii,jdeb,jfin,jj,direc,tag
40!      integer :: MPI_COMM_WORLD
41
42       integer :: jj2,from,jj3   
43  integer, dimension(MPI_STATUS_SIZE) :: status
44       
45      call MPI_COMM_RANK ( MPI_COMM_WORLD, myid, ierr )
46      call MPI_COMM_SIZE ( MPI_COMM_WORLD, ntasks, ierr )
47     if (direc.eq.0) then ! the slaves get
48
49      if (myid.eq.0) then
50       do ii=1,ntasks-1
51       do jj2=1,chunksize
52        jj=(jj2-1)*ntasks+ii+1
53!       do jj=ii+1,numpart2+ii,ntasks
54!        jj2=(jj-ii-1)/ntasks+1
55!        dummyi2(jj2)=dummyi(jj)
56        if (tag.eq.13) dummyi22(jj2)=cbt(jj)
57        enddo
58    call MPI_SEND(dummyi22, chunksize, MPI_INTEGER2, ii,tag, MPI_COMM_WORLD, ierr)
59       enddo
60!     chunksize2=int((numpart2-1)/ntasks)+1
61!     chunksize2=chunksize
62      ii=0
63      do jj=1,numpart2,ntasks
64      ii=ii+1
65      jj2=jj
66      enddo
67      chunksize2=ii+numpart2-jj2
68
69    if (tag.eq.13) then
70     do jj=1,numpart2,ntasks
71      jj3=(jj-1)/ntasks+1
72     mpi_cbt(jj3)=cbt(jj)
73     enddo
74     mpi_cbt(jj3:chunksize2)=cbt(jj2:numpart2)
75
76    endif
77
78   else ! the slaves receive
79    if (tag.eq.13) call MPI_RECV(mpi_cbt, chunksize, MPI_INTEGER2, 0,13, MPI_COMM_WORLD,status, ierr)
80   endif
81
82   else ! the master is going to get
83   if (myid.gt.0) then !slaves send
84   if (tag.eq.13) call MPI_SEND(mpi_cbt, chunksize, MPI_INTEGER2, 0,13, MPI_COMM_WORLD, ierr)
85
86    else ! the master gets
87     do from =1,ntasks-1
88    call MPI_RECV(dummyi22, chunksize, MPI_INTEGER2, from,tag, MPI_COMM_WORLD,status,ierr)
89          jj1=(from-1)*chunksize+1
90          jj2=from*chunksize
91       if (tag.eq.13) cbt(jj1:jj2)=dummyi22(1:chunksize)
92     enddo
93     if (tag.eq.13) cbt(jj2+1:numpart2)=mpi_cbt(1:chunksize2)
94
95    endif
96
97   endif
98
99       end subroutine sendint2_mpi
Note: See TracBrowser for help on using the repository browser.
hosted by ZAMG