source: CONFIG/UNIFORM/v6/IPSLCM6.5/SOURCES/OASIS3-MCT/m_AttrVectComms.F90 @ 5066

Last change on this file since 5066 was 5066, checked in by cetlod, 4 years ago

First step towards IPSLCM6.5 with the use of NEMOv4 model

File size: 52.1 KB
Line 
1!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!    Math and Computer Science Division, Argonne National Laboratory   !
3!-----------------------------------------------------------------------
4! CVS m_AttrVectComms.F90,v 1.39 2009-03-05 16:41:47 jacob Exp
5! CVS MCT_2_8_0
6!BOP -------------------------------------------------------------------
7!
8! !MODULE: m_AttrVectComms - MPI Communications Methods for the AttrVect
9!
10! !DESCRIPTION:
11!
12! This module defines the communications methods for the {\tt AttrVect}
13! datatype (see the module {\tt m\_AttrVect} for more information about
14! this class and its methods).  MCT's communications are implemented
15! in terms of the Message Passing Interface (MPI) standard, and we have
16! as best as possible, made the interfaces to these routines appear as
17! similar as possible to the corresponding MPI routines.  For the
18! { \tt AttrVect}, we supply {\em blocking} point-to-point send and
19! receive operations.  We also supply the following collective
20! operations: broadcast, gather, and scatter.  The gather and scatter
21! operations rely on domain decomposition descriptors that are defined
22! elsewhere in MCT:  the {\tt GlobalMap}, which is a one-dimensional
23! decomposition (see the MCT module {\tt m\_GlobalMap} for more details);
24! and the {\tt GlobalSegMap}, which is a segmented decomposition capable
25! of supporting multidimensional domain decompositions (see the MCT module
26! {\tt m\_GlobalSegMap} for more details).
27!
28! !INTERFACE:
29 module m_AttrVectComms
30!
31! !USES:
32!
33      use m_AttrVect ! AttrVect class and its methods
34
35      implicit none
36
37      private   ! except
38
39      public :: gather          ! gather all local vectors to the root
40      public :: scatter         ! scatter from the root to all PEs
41      public :: bcast           ! bcast from root to all PEs
42      public :: send            ! send an AttrVect
43      public :: recv            ! receive an AttrVect
44
45    interface gather ; module procedure &
46              GM_gather_, &
47              GSM_gather_ 
48    end interface
49    interface scatter ; module procedure &
50              GM_scatter_, &
51              GSM_scatter_ 
52    end interface
53    interface bcast  ; module procedure bcast_  ; end interface
54    interface send  ; module procedure send_  ; end interface
55    interface recv  ; module procedure recv_  ; end interface
56
57! !REVISION HISTORY:
58! 27Oct00 - J.W. Larson <larson@mcs.anl.gov> - relocated routines
59!           from m_AttrVect to create this module.
60! 15Jan01 - J.W. Larson <larson@mcs.anl.gov> - Added APIs for
61!           GSM_gather_() and GSM_scatter_().
62!  9May01 - J.W. Larson <larson@mcs.anl.gov> - Modified GM_scatter_
63!           so its communication model agrees with MPI_scatter().
64!           Also tidied up prologues in all module routines.
65!  7Jun01 - J.W. Larson <larson@mcs.anl.gov> - Added send()
66!           and recv().
67!  3Aug01 - E.T. Ong <eong@mcs.anl.gov> - in GSM_scatter, call
68!           GlobalMap_init with actual shaped array to satisfy
69!           Fortran 90 standard. See comment in subroutine.
70! 23Aug01 - E.T. Ong <eong@mcs.anl.gov> - replaced assignment(=)
71!           with copy for list type to avoid compiler bugs in pgf90.
72!           Added more error checking in gsm scatter. Fixed minor bugs
73!          in gsm and gm gather.
74! 13Dec01 - E.T. Ong <eong@mcs.anl.gov> - GSM_scatter, allow users
75!           to scatter with a haloed GSMap. Fixed some bugs in
76!           GM_scatter.
77! 19Dec01 - E.T. Ong <eong@mcs.anl.gov> - allow bcast of an AttrVect
78!           with only an integer or real attribute.
79! 27Mar02 - J.W. Larson <larson@mcs.anl.gov> - Corrected usage of
80!           m_die routines throughout this module.
81!EOP ___________________________________________________________________
82
83  character(len=*),parameter :: myname='MCT::m_AttrVectComms'
84
85 contains
86
87!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
88!    Math and Computer Science Division, Argonne National Laboratory   !
89!BOP -------------------------------------------------------------------
90!
91! !IROUTINE: send_ - Point-to-point Send of an AttrVect
92!
93! !DESCRIPTION:  This routine takes an input {\tt AttrVect} argument
94! {\tt inAV} and sends it to processor {\tt dest} on the communicator
95! associated with the Fortran {\tt INTEGER} MPI communicator handle
96! {\tt comm}.  The overalll message is tagged by the input {\tt INTEGER}
97! argument {\tt TagBase}.  The success (failure) of this operation is
98! reported in the zero (nonzero) optional output argument {\tt status}.
99!
100! {\bf N.B.}:  One must avoid assigning elsewhere the MPI tag values
101! between {\tt TagBase} and {\tt TagBase+7}, inclusive.  This is
102! because {\tt send\_()} performs the send of the {\tt AttrVect} as
103! a series of eight send operations.
104!
105! !INTERFACE:
106
107 subroutine send_(inAV, dest, TagBase, comm, status)
108!
109! !USES:
110!
111      use m_stdio
112      use m_mpif90
113      use m_die
114
115      use m_List, only : List
116      use m_List, only : List_allocated => allocated
117      use m_List, only : List_nitem => nitem
118      use m_List, only : List_send => send
119
120      use m_AttrVect, only : AttrVect
121      use m_AttrVect, only : AttrVect_lsize => lsize
122
123      implicit none
124
125! !INPUT PARAMETERS:
126!
127      type(AttrVect),     intent(in)  :: inAV
128      integer,            intent(in)  :: dest
129      integer,            intent(in)  :: TagBase
130      integer,            intent(in)  :: comm
131
132! !OUTPUT PARAMETERS:
133!
134      integer, optional,  intent(out) :: status
135
136! !REVISION HISTORY:
137!  7Jun01 - J.W. Larson - initial version.
138! 13Jun01 - J.W. Larson <larson@mcs.anl.gov> - Initialize status
139!           (if present).
140!EOP ___________________________________________________________________
141
142 character(len=*),parameter :: myname_=myname//'::send_'
143
144 logical :: ListAssoc(2)
145 integer :: ierr
146 integer :: AVlength
147
148      ! Initialize status (if present)
149
150  if(present(status)) status = 0
151
152
153       ! Step 1. Are inAV%iList and inAV%rList filled?  Store
154       ! the answers in the LOGICAL array ListAssoc and send.
155
156  ListAssoc(1) = List_allocated(inAV%iList) 
157  ListAssoc(2) = List_allocated(inAV%rList) 
158
159  if(.NOT. (ListAssoc(1).or.ListAssoc(2)) ) then
160     call die(myname_,"inAV has not been initialized")
161  endif
162     
163  call MPI_SEND(ListAssoc, 2, MP_LOGICAL, dest, TagBase, comm, ierr)
164  if(ierr /= 0) then
165     call MP_perr_die(myname_,':: MPI_SEND(ListAssoc...',ierr)
166  endif
167
168
169       ! Step 2. Send non-blank inAV%iList and inAV%rList.
170
171  if(ListAssoc(1)) then
172    call List_send(inAV%iList, dest, TagBase+1, comm, ierr)
173    if(ierr /= 0) then
174       if(present(status)) then
175          write(stderr,*) myname_,':: call List_send(inAV%iList...'
176          status = ierr
177          return
178       else
179          call die(myname_,':: call List_send(inAV%iList...',ierr)
180       endif
181    endif
182  endif
183
184  if(ListAssoc(2)) then
185    call List_send(inAV%rList, dest, TagBase+3, comm, ierr)
186    if(ierr /= 0) then
187       if(present(status)) then
188          write(stderr,*) myname_,':: call List_send(inAV%rList...'
189          status = ierr
190          return
191       else
192          call die(myname_,':: call List_send(inAV%rList...',ierr)
193       endif
194    endif
195  endif
196
197       ! Step 3. Determine and send the lengths of inAV%iAttr(:,:)
198       ! and inAV%rAttr(:,:).
199
200  AVlength = AttrVect_lsize(inAV)
201
202  if(AVlength<=0) then
203     call die(myname_,"Size of inAV <= 0",AVLength)
204  endif
205
206  call MPI_SEND(AVlength, 1, MP_type(AVlength), dest, TagBase+5, &
207                comm, ierr)
208  if(ierr /= 0) then
209     call MP_perr_die(myname_,':: call MPI_SEND(AVlength...',ierr)
210  endif
211
212       ! Step 4. If AVlength > 0, we may have INTEGER and REAL
213       ! data to send.  Send as needed.
214
215  if(AVlength > 0) then
216
217     if(ListAssoc(1)) then
218
219       ! Send the INTEGER data stored in inAV%iAttr(:,:)
220
221        call MPI_SEND(inAV%iAttr(1,1), AVlength*List_nitem(inAV%iList), &
222                      MP_type(inAV%iAttr(1,1)), dest, TagBase+6,   &
223                      comm, ierr)
224        if(ierr /= 0) then
225           call MP_perr_die(myname_,':: call MPI_SEND(inAV%iAttr...',ierr)
226        endif
227
228     endif ! if(associated(inAV%rList))
229
230     if(ListAssoc(2)) then
231
232       ! Send the REAL data stored in inAV%rAttr(:,:)
233
234        call MPI_SEND(inAV%rAttr(1,1), AVlength*List_nitem(inAV%rList), &
235                      MP_type(inAV%rAttr(1,1)), dest, TagBase+7,   &
236                      comm, ierr)
237        if(ierr /= 0) then
238           call MP_perr_die(myname_,':: call MPI_SEND(inAV%rAttr...',ierr)
239        endif
240
241     endif ! if(associated(inAV%rList))
242
243  endif ! if (AVlength > 0)
244
245 end subroutine send_
246
247!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
248!    Math and Computer Science Division, Argonne National Laboratory   !
249!BOP -------------------------------------------------------------------
250!
251! !IROUTINE: recv_ - Point-to-point Receive of an AttrVect
252!
253! !DESCRIPTION:  This routine receives the output {\tt AttrVect} argument
254! {\tt outAV} from processor {\tt source} on the communicator associated
255! with the Fortran {\tt INTEGER} MPI communicator handle {\tt comm}.  The
256! overall message is tagged by the input {\tt INTEGER} argument
257! {\tt TagBase}.  The success (failure) of this operation is reported in
258! the zero (nonzero) optional output argument {\tt status}.
259!
260! {\bf N.B.}:  One must avoid assigning elsewhere the MPI tag values
261! between {\tt TagBase} and {\tt TagBase+7}, inclusive.  This is
262! because {\tt recv\_()} performs the receive of the {\tt AttrVect} as
263! a series of eight receive operations.
264!
265! !INTERFACE:
266
267 subroutine recv_(outAV, dest, TagBase, comm, status)
268!
269! !USES:
270!
271      use m_stdio
272      use m_mpif90
273      use m_die
274
275      use m_List, only : List
276      use m_List, only : List_nitem => nitem
277      use m_List, only : List_recv => recv
278
279      use m_AttrVect, only : AttrVect
280
281      implicit none
282
283! !INPUT PARAMETERS:
284!
285      integer,            intent(in)  :: dest
286      integer,            intent(in)  :: TagBase
287      integer,            intent(in)  :: comm
288
289! !OUTPUT PARAMETERS:
290!
291      type(AttrVect),     intent(out) :: outAV
292      integer, optional,  intent(out) :: status
293
294! !REVISION HISTORY:
295!  7Jun01 - J.W. Larson - initial working version.
296! 13Jun01 - J.W. Larson <larson@mcs.anl.gov> - Initialize status
297!           (if present).
298!EOP ___________________________________________________________________
299
300 character(len=*),parameter :: myname_=myname//'::recv_'
301
302 logical :: ListAssoc(2)
303 integer :: ierr
304 integer :: AVlength
305 integer :: MPstatus(MP_STATUS_SIZE)
306
307      ! Initialize status (if present)
308
309  if(present(status)) status = 0
310
311
312       ! Step 1. Are outAV%iList and outAV%rList filled?  TRUE
313       ! entries in the LOGICAL array ListAssoc(:) correspond
314       ! to Non-blank Lists...that is:
315       !
316       ! ListAssoc(1) = .TRUE. <==> associated(outAV%iList%bf)
317       ! ListAssoc(2) = .TRUE. <==> associated(outAV%rList%bf)
318
319  call MPI_RECV(ListAssoc, 2, MP_LOGICAL, dest, TagBase, comm, &
320                MPstatus, ierr)
321  if(ierr /= 0) then
322     call MP_perr_die(myname_,':: MPI_RECV(ListAssoc...',ierr)
323  endif
324
325
326       ! Step 2. Receive non-blank outAV%iList and outAV%rList.
327
328  if(ListAssoc(1)) then
329    call List_recv(outAV%iList, dest, TagBase+1, comm, ierr)
330    if(ierr /= 0) then
331       if(present(status)) then
332          write(stderr,*) myname_,':: call List_recv(outAV%iList...'
333          status = ierr
334          return
335       else
336          call die(myname_,':: call List_recv(outAV%iList...',ierr)
337       endif
338    endif
339  endif
340
341  if(ListAssoc(2)) then
342    call List_recv(outAV%rList, dest, TagBase+3, comm, ierr)
343    if(ierr /= 0) then
344       if(present(status)) then
345          write(stderr,*) myname_,':: call List_recv(outAV%rList...'
346          status = ierr
347          return
348       else
349          call die(myname_,':: call List_recv(outAV%rList...',ierr)
350       endif
351    endif
352  endif
353
354       ! Step 3. Receive the lengths of outAV%iAttr(:,:) and outAV%rAttr(:,:).
355
356  call MPI_RECV(AVlength, 1, MP_type(AVlength), dest, TagBase+5, &
357                comm, MPstatus, ierr)
358  if(ierr /= 0) then
359     call MP_perr_die(myname_,':: call MPI_RECV(AVlength...',ierr)
360  endif
361
362       ! Step 4. If AVlength > 0, we may have to receive INTEGER
363       ! and/or REAL data.  Receive as needed.
364
365  if(AVlength > 0) then
366
367     if(ListAssoc(1)) then
368
369       ! Allocate outAV%iAttr(:,:)
370
371        allocate(outAV%iAttr(List_nitem(outAV%iList),AVlength), stat=ierr)
372        if(ierr/=0) call die(myname_,"allocate(outAV%iAttr)",ierr)
373
374       ! Receive the INTEGER data to outAV%iAttr(:,:)
375
376        call MPI_RECV(outAV%iAttr(1,1), AVlength*List_nitem(outAV%iList), &
377                      MP_type(outAV%iAttr(1,1)), dest, TagBase+6,   &
378                      comm, MPstatus, ierr)
379        if(ierr /= 0) then
380           call MP_perr_die(myname_,':: call MPI_RECV(outAV%iAttr...',ierr)
381        endif
382
383     endif ! if(associated(outAV%rList))
384
385     if(ListAssoc(2)) then
386
387       ! Allocate outAV%rAttr(:,:)
388
389        allocate(outAV%rAttr(List_nitem(outAV%rList),AVlength), stat=ierr)
390        if(ierr/=0) call die(myname_,"allocate(outAV%rAttr)",ierr)
391
392       ! Receive the REAL data to outAV%rAttr(:,:)
393
394        call MPI_RECV(outAV%rAttr(1,1), AVlength*List_nitem(outAV%rList), &
395                      MP_type(outAV%rAttr(1,1)), dest, TagBase+7,   &
396                      comm, MPstatus, ierr)
397        if(ierr /= 0) then
398           call MP_perr_die(myname_,':: call MPI_RECV(outAV%rAttr...',ierr)
399        endif
400
401     endif ! if(associated(outAV%rList))
402
403  endif ! if (AVlength > 0)
404
405 end subroutine recv_
406
407!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
408!    Math and Computer Science Division, Argonne National Laboratory   !
409!BOP -------------------------------------------------------------------
410!
411! !IROUTINE: GM_gather_ - Gather an AttrVect Distributed by a GlobalMap
412!
413! !DESCRIPTION:
414! This routine gathers a {\em distributed} {\tt AttrVect} {\tt iV} to
415! the {\tt root} process, and returns it in the output {\tt AttrVect}
416! argument {\tt oV}.  The decomposition of {\tt iV} is described by
417! the input {\tt GlobalMap} argument {\tt GMap}.  The input {\tt INTEGER}
418! argument {\tt comm} is the Fortran integer MPI communicator handle.
419! The success (failure) of this operation corresponds to a zero (nonzero)
420! value of the optional output {\tt INTEGER} argument {\tt stat}.
421!
422! !INTERFACE:
423
424 subroutine GM_gather_(iV, oV, GMap, root, comm, stat)
425!
426! !USES:
427!
428      use m_stdio
429      use m_die
430      use m_mpif90
431      use m_realkinds, only : FP
432      use m_GlobalMap, only : GlobalMap
433      use m_GlobalMap, only : GlobalMap_lsize => lsize
434      use m_GlobalMap, only : GlobalMap_gsize => gsize
435      use m_AttrVect, only : AttrVect
436      use m_AttrVect, only : AttrVect_init => init
437      use m_AttrVect, only : AttrVect_zero => zero 
438      use m_AttrVect, only : AttrVect_lsize => lsize
439      use m_AttrVect, only : AttrVect_nIAttr => nIAttr
440      use m_AttrVect, only : AttrVect_nRAttr => nRAttr
441      use m_AttrVect, only : AttrVect_clean => clean
442      use m_FcComms,  only : fc_gatherv_int, fc_gatherv_fp
443
444      implicit none
445
446! !INPUT PARAMETERS:
447!
448      type(AttrVect),           intent(in)  :: iV
449      type(GlobalMap),          intent(in)  :: GMap
450      integer,                  intent(in)  :: root
451      integer,                  intent(in)  :: comm
452
453! !OUTPUT PARAMETERS:
454!
455      type(AttrVect),           intent(out) :: oV
456      integer,        optional, intent(out) :: stat
457
458! !REVISION HISTORY:
459! 15Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
460! 27Oct00 - J.W. Larson <larson@mcs.anl.gov> - relocated from
461!           m_AttrVect
462! 15Jan01 - J.W. Larson <larson@mcs.anl.gov> - renamed GM_gather_
463!  9May01 - J.W. Larson <larson@mcs.anl.gov> - tidied up prologue
464! 18May01 - R.L. Jacob <jacob@mcs.anl.gov> - use MP_Type function
465!           to determine type for mpi_gatherv
466! 31Jan09 - P.H. Worley <worleyph@ornl.gov> - replaced call to
467!           MPI_gatherv with call to flow controlled gather routines
468!EOP ___________________________________________________________________
469
470  character(len=*),parameter :: myname_=myname//'::GM_gather_'
471  integer :: nIA,nRA,niV,noV,ier
472  integer :: myID
473  integer :: mp_type_Av
474  type(AttrVect) :: nonRootAV
475
476  if(present(stat)) stat=0
477
478  call MP_comm_rank(comm, myID, ier)
479  if(ier /= 0) then
480     call MP_perr_die(myname_,':: call MP_COMM_RANK()',ier)
481  endif
482
483        ! Verify the input: a _scatterd_ vector
484
485  niV=GlobalMap_lsize(GMap)
486  noV=AttrVect_lsize(iV)
487
488  if(niV /= noV) then
489     write(stderr,'(2a,i4,a,i4,a,i4)') myname_, &
490          ': invalid input, lsize(GMap) =',niV, &
491          ', lsize(iV) =',noV, 'myID =', myID
492     if(.not.present(stat)) call die(myname_)
493     stat=-1
494     return
495  endif
496
497  noV=GlobalMap_gsize(GMap) ! the gathered local size, as for the output
498
499  if(myID == root) then
500     call AttrVect_init(oV,iV,noV)
501     call AttrVect_zero(oV)
502  else
503     call AttrVect_init(nonRootAV,iV,1)
504     call AttrVect_zero(nonRootAV)
505  endif
506
507  niV=GlobalMap_lsize(GMap) ! the scattered local size, as for the input
508
509  nIA=AttrVect_nIAttr(iV)       ! number of INTEGER attributes
510  nRA=AttrVect_nRAttr(iV)       ! number of REAL attributes
511
512  mp_type_Av = MP_Type(1._FP)   ! set mpi type to same as AV%rAttr
513
514  if(nIA > 0) then
515     
516     if(myID == root) then
517
518        call fc_gatherv_int(iV%iAttr,niV*nIA,MP_INTEGER,                &
519             oV%iAttr,GMap%counts*nIA,GMap%displs*nIA,             &
520             MP_INTEGER,root,comm)
521
522     else
523       
524        call fc_gatherv_int(iV%iAttr,niV*nIA,MP_INTEGER,                &
525             nonRootAV%iAttr,GMap%counts*nIA,GMap%displs*nIA,      &
526             MP_INTEGER,root,comm)
527
528     endif  ! if(myID == root)
529       
530  endif  ! if(nIA > 0)
531
532  if(nRA > 0) then
533
534     if(myID == root) then
535
536        call fc_gatherv_fp(iV%rAttr,niV*nRA,mp_type_Av,         &
537             oV%rAttr,GMap%counts*nRA,GMap%displs*nRA,             & 
538             mp_type_Av,root,comm)
539
540     else
541
542        call fc_gatherv_fp(iV%rAttr,niV*nRA,mp_type_Av,         &
543             nonRootAV%rAttr,GMap%counts*nRA,GMap%displs*nRA,      &
544             mp_type_Av,root,comm)
545
546     endif  ! if(myID == root)
547
548  endif  ! if(nRA > 0)
549
550
551
552  if(myID /= root) then
553     call AttrVect_clean(nonRootAV,ier)
554     if(ier /= 0) then
555        write(stderr,'(2a,i4)') myname_,        &
556             ':: AttrVect_clean(nonRootAV) failed for non-root &
557             &process: myID = ', myID
558        call die(myname_,':: AttrVect_clean failed &
559             &for nonRootAV off of root',ier)
560     endif
561  endif
562
563 end subroutine GM_gather_
564
565!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
566!    Math and Computer Science Division, Argonne National Laboratory   !
567!BOP -------------------------------------------------------------------
568!
569! !IROUTINE: GSM_gather_ - Gather an AttrVect Distributed by a GlobalSegMap
570!
571! !DESCRIPTION:
572! The routine {\tt GSM\_gather\_()} takes a distributed input
573! {\tt AttrVect} argument {\tt iV}, whose decomposition is described
574! by the input {\tt GlobalSegMap} argument {\tt GSMap}, and gathers
575! it to the output {\tt AttrVect} argument {\tt oV}.  The gathered
576! {\tt AttrVect} {\tt oV} is valid only on the root process specified
577! by the input argument {\tt root}.  The communicator used to gather
578! the data is specified by the argument {\tt comm}.  The success (failure)
579! is reported in the zero (non-zero) value of the output argument
580! {\tt stat}.
581!
582! {\tt GSM\_gather\_()} converts the problem of gathering data
583! according to a {\tt GlobalSegMap} into the simpler problem of
584! gathering data as specified by a {\tt GlobalMap}.  The {\tt GlobalMap}
585! variable {\tt GMap} is created based on the local storage requirements
586! for each distributed piece of {\tt iV}.  On the root, a complete
587! (including halo points) gathered copy of {\tt iV} is collected into
588! the temporary {\tt AttrVect} variable {\tt workV} (the length of
589! {\tt workV} is the larger of {\tt GlobalSegMap\_GlobalStorage(GSMap)} or
590! {\tt GlobalSegMap\_GlobalSize(GSMap)}).  The
591! variable {\tt workV} is segmented by process, and segments are
592! copied into it by process, but ordered in the same order the segments
593! appear in {\tt GSMap}.  Once {\tt workV} is loaded, the data are
594! copied segment-by-segment to their appropriate locations in the output
595! {\tt AttrVect} {\tt oV}.
596!
597! !INTERFACE:
598
599 subroutine GSM_gather_(iV, oV, GSMap, root, comm, stat, rdefault, idefault)
600!
601! !USES:
602!
603! Message-passing environment utilities (mpeu) modules:
604      use m_stdio
605      use m_die
606      use m_mpif90
607      use m_realkinds, only: FP
608! GlobalSegMap and associated services:
609      use m_GlobalSegMap, only : GlobalSegMap
610      use m_GlobalSegMap, only : GlobalSegMap_comp_id => comp_id
611      use m_GlobalSegMap, only : GlobalSegMap_ngseg => ngseg
612      use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
613      use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
614      use m_GlobalSegMap, only : GlobalSegMap_haloed => haloed
615      use m_GlobalSegMap, only : GlobalSegMap_GlobalStorage => GlobalStorage
616! AttrVect and associated services:
617      use m_AttrVect, only : AttrVect
618      use m_AttrVect, only : AttrVect_init => init
619      use m_AttrVect, only : AttrVect_zero => zero
620      use m_AttrVect, only : AttrVect_lsize => lsize
621      use m_AttrVect, only : AttrVect_nIAttr => nIAttr
622      use m_AttrVect, only : AttrVect_nRAttr => nRAttr
623      use m_AttrVect, only : AttrVect_clean => clean 
624! GlobalMap and associated services:
625      use m_GlobalMap, only : GlobalMap
626      use m_GlobalMap, only : GlobalMap_init => init
627      use m_GlobalMap, only : GlobalMap_clean => clean
628
629      implicit none
630
631! !INPUT PARAMETERS:
632!
633      type(AttrVect),            intent(in)  :: iV
634      type(GlobalSegMap),        intent(in)  :: GSMap
635      integer,                   intent(in)  :: root
636      integer,                   intent(in)  :: comm
637      real(FP), optional,        intent(in)  :: rdefault
638      integer, optional,         intent(in)  :: idefault
639
640! !OUTPUT PARAMETERS:
641!
642      type(AttrVect),            intent(out) :: oV
643      integer,        optional,  intent(out) :: stat
644
645! !REVISION HISTORY:
646! 15Jan01 - J.W. Larson <larson@mcs.anl.gov> - API specification.
647! 25Feb01 - J.W. Larson <larson@mcs.anl.gov> - Prototype code.
648! 26Apr01 - R.L. Jacob <jacob@mcs.anl.gov> - add use statement for
649!           AttVect_clean
650!  9May01 - J.W. Larson <larson@mcs.anl.gov> - tidied up prologue
651! 13Jun01 - J.W. Larson <larson@mcs.anl.gov> - Initialize stat
652!           (if present).
653! 20Aug01 - E.T. Ong <eong@mcs.anl.gov> - Added error checking for
654!           matching processors in gsmap and comm. Corrected
655!           current_pos assignment.
656! 23Nov01 - R. Jacob <jacob@mcs.anl.gov> - zero the oV before copying in
657!           gathered data.
658! 27Jul07 - R. Loy <rloy@mcs.anl.gov> - add Tony's suggested improvement
659!           for a default value in the output AV
660! 11Aug08 - R. Jacob <jacob@mcs.anl.gov> - add Pat Worley's faster way
661!           to initialize lns
662!EOP ___________________________________________________________________
663
664  character(len=*),parameter :: myname_=myname//'::GSM_gather_'
665
666! Temporary workspace AttrVect:
667  type(AttrVect) :: workV
668! Component ID and number of segments for GSMap:
669  integer :: comp_id, ngseg, iseg
670! Total length of GSMap segments laid end-to-end:
671  integer :: global_storage
672! Error Flag
673  integer :: ierr
674! Number of processes on communicator, and local rank:
675  integer :: NumProcs, myID
676! Total local storage on each pe according to GSMap:
677  integer, dimension(:), allocatable :: lns
678! Temporary GlobalMap used to scatter the segmented (by pe) data
679  type(GlobalMap) :: workGMap
680! Loop counters and temporary indices:
681  integer :: m, n, ilb, iub, olb, oub, pe
682! workV segment tracking index array:
683  integer, dimension(:), allocatable :: current_pos
684! workV sizes
685  integer :: gssize, gstorage
686
687      ! Initialize stat (if present)
688
689  if(present(stat)) stat = 0
690
691       ! Initial Check:  If GSMap contains halo points, die
692!CE
693! It has been suggested to comment out the test that triggers the error in
694! lib/mct/mct/m_AttrVectComms.F90, and that works in my case
695! Eric Maisonnave had exactly the same problem at the MetOffice and he did exactly
696!  what you did. There is a ticket opened on the problem #2472 and we work on it       
697!
698!  if(GlobalSegMap_haloed(GSMap)) then
699!     ierr = 1
700!     call die(myname_,"Input GlobalSegMap haloed--not allowed",ierr)
701!  endif
702!CE
703
704       ! Which process am I?
705
706  call MPI_COMM_RANK(comm, myID, ierr)
707
708  if(ierr /= 0) then
709        call MP_perr_die(myname_,':: call MPI_COMM_RANK()',ierr)
710  endif
711       ! How many processes are there on this communicator?
712
713  call MPI_COMM_SIZE(comm, NumProcs, ierr)
714
715  if(ierr /= 0) then
716     call MP_perr_die(myname_,':: call MPI_COMM_SIZE()',ierr)
717  endif
718
719       ! Processor Check: Do the processors on GSMap match those in comm?
720
721  if(MAXVAL(GSMap%pe_loc) > (NumProcs-1)) then
722     stat=2
723     write(stderr,*) myname_, &
724       ":: Procs in GSMap%pe_loc do not match procs in communicator ", &
725       NumProcs-1, MAXVAL(GSMap%pe_loc)
726     call die(myname_, &
727          "Procs in GSMap%pe_loc do not match procs in communicator",stat)
728  endif
729
730  if(myID == root) then
731
732       ! Allocate a precursor to a GlobalMap accordingly...
733
734     allocate(lns(0:NumProcs-1), stat=ierr)
735
736       ! And Load it...
737
738     lns(:)=0
739     do iseg=1,GSMap%ngseg
740        n = GSMap%pe_loc(iseg)
741        lns(n) = lns(n) + GSMap%length(iseg)
742     end do
743
744  else
745
746     allocate(lns(0)) ! This conforms to F90 standard for shaped arguments.
747
748  endif ! if(myID == root)
749
750       ! Determine the component id of GSMap:
751
752  comp_id = GlobalSegMap_comp_id(GSMap)
753
754       ! Create working GlobalMap workGMap (used for the gather):
755
756  call GlobalMap_init(workGMap, comp_id, lns, root, comm)
757
758       ! Gather the Data process-by-process to workV...
759       ! do not include stat argument; bypass an argument check in gm_gather.
760
761  call GM_gather_(iV, workV, workGMap, root, comm, stat)
762
763       ! On the root, initialize oV, and load the contents of
764       !workV into it...
765
766  if(myID == root) then
767
768! bug fix:  gstorage will be bigger than gssize if GSmap is
769! haloed.  But gstorage may be smaller than gsize if GSmap
770! is masked.  So take the maximum.  RLJ
771     gstorage = GlobalSegMap_GlobalStorage(GSMap)
772     gssize = GlobalSegMap_gsize(GSMap)
773     global_storage = MAX(gstorage,gssize)
774
775     call AttrVect_init(oV,iV,global_storage)
776     call AttrVect_zero(oV)
777
778     if (present(rdefault)) then
779       if (AttrVect_nRAttr(oV) > 0) oV%rAttr=rdefault
780     endif
781     if (present(idefault)) then
782       if (AttrVect_nIAttr(oV) > 0) oV%iAttr=idefault
783     endif
784
785       ! On the root, allocate current position index for
786       ! each process chunk:
787
788     allocate(current_pos(0:NumProcs-1), stat=ierr)
789
790     if(ierr /= 0) then
791        write(stderr,*) myname_,':: allocate(current_pos(..) failed,', &
792             'stat = ',ierr
793        if(present(stat)) then
794           stat=ierr
795        else
796           call die(myname_,'allocate(current_pos(..) failed.' )
797        endif
798     endif
799
800       ! Initialize current_pos(:) using GMap%displs(:)
801
802     do n=0,NumProcs-1
803        current_pos(n) = workGMap%displs(n) + 1
804     end do
805
806       ! Load each segment of iV into its appropriate segment
807       ! of workV:
808     
809     ngseg = GlobalSegMap_ngseg(GSMap)
810
811     do n=1,ngseg
812
813       ! Determine which process owns segment n:
814
815        pe = GSMap%pe_loc(n)
816
817       ! Input map (lower/upper indicess) of segment of iV:
818
819        ilb = current_pos(pe)
820        iub = current_pos(pe) + GSMap%length(n) - 1
821
822       ! Output map of (lower/upper indicess) segment of workV:
823
824        olb = GSMap%start(n)
825        oub = GSMap%start(n) + GSMap%length(n) - 1
826
827       ! Increment current_pos(n) for next time:
828
829        current_pos(pe) = current_pos(pe) + GSMap%length(n)
830
831       ! Now we are equipped to do the copy:
832
833        do m=1,AttrVect_nIAttr(iV)
834           oV%iAttr(m,olb:oub) = workV%iAttr(m,ilb:iub)
835        end do
836
837        do m=1,AttrVect_nRAttr(iV)
838           oV%rAttr(m,olb:oub) = workV%rAttr(m,ilb:iub)
839        end do
840
841     end do ! do n=1,ngseg
842
843       ! Clean up current_pos, which was only allocated on the root
844
845     deallocate(current_pos, stat=ierr)
846     if(ierr /= 0) then
847        write(stderr,*) myname_,'error in deallocate(current_pos), stat=',ierr
848        if(present(stat)) then
849           stat=ierr
850        else
851           call die(myname_)
852        endif
853     endif
854  endif ! if(myID == root)
855
856       ! At this point, we are finished.  The data have been gathered
857       ! to oV
858
859       ! Finally, clean up allocated structures:
860
861  if(myID == root) call AttrVect_clean(workV)
862  call GlobalMap_clean(workGMap)
863
864  deallocate(lns, stat=ierr)
865
866  if(ierr /= 0) then
867    write(stderr,*) myname_,'error in deallocate(lns), stat=',ierr
868    if(present(stat)) then
869       stat=ierr
870    else
871       call die(myname_)
872    endif
873  endif
874
875 end subroutine GSM_gather_
876
877!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
878!    Math and Computer Science Division, Argonne National Laboratory   !
879!BOP -------------------------------------------------------------------
880!
881! !IROUTINE: GM_scatter_ - Scatter an AttrVect Using a GlobalMap
882!
883! !DESCRIPTION:
884! The routine {\tt GM\_scatter\_} takes an input {\tt AttrVect} type
885! {\tt iV} (valid only on the root), and scatters it to a distributed
886! {\tt AttrVect} {\tt oV}.  The input {\tt GlobalMap} argument
887! {\tt GMap} dictates how {\tt iV} is scattered to {\tt oV}.  The
888! success (failure) of this routine is reported in the zero (non-zero)
889! value of the output argument {\tt stat}.
890!
891! {\bf N.B.}:  The output {\tt AttrVect} argument {\tt oV} represents
892! dynamically allocated memory.  When it is no longer needed, it should
893! be deallocated by invoking {\tt AttrVect\_clean()} (see the module
894! {\tt m\_AttrVect} for more details).
895!
896! !INTERFACE:
897
898 subroutine GM_scatter_(iV, oV, GMap, root, comm, stat)
899!
900! !USES:
901!
902      use m_stdio
903      use m_die
904      use m_mpif90
905      use m_realkinds, only : FP
906
907      use m_List, only : List
908      use m_List, only : List_copy => copy
909      use m_List, only : List_bcast => bcast
910      use m_List, only : List_clean => clean
911      use m_List, only : List_nullify => nullify
912      use m_List, only : List_nitem => nitem
913
914      use m_GlobalMap, only : GlobalMap
915      use m_GlobalMap, only : GlobalMap_lsize => lsize
916      use m_GlobalMap, only : GlobalMap_gsize => gsize
917
918      use m_AttrVect, only : AttrVect
919      use m_AttrVect, only : AttrVect_init => init
920      use m_AttrVect, only : AttrVect_zero => zero
921      use m_AttrVect, only : AttrVect_lsize => lsize
922      use m_AttrVect, only : AttrVect_nIAttr => nIAttr
923      use m_AttrVect, only : AttrVect_nRAttr => nRAttr
924      use m_AttrVect, only : AttrVect_clean => clean
925
926      implicit none
927
928! !INPUT PARAMETERS:
929!
930      type(AttrVect),           intent(in)  :: iV
931      type(GlobalMap),          intent(in)  :: GMap
932      integer,                  intent(in)  :: root
933      integer,                  intent(in)  :: comm
934
935! !OUTPUT PARAMETERS:
936!
937      type(AttrVect),           intent(out) :: oV
938      integer,        optional, intent(out) :: stat
939
940! !REVISION HISTORY:
941! 21Apr98 - Jing Guo <guo@thunder> - initial prototype/prolog/code
942! 27Oct00 - J.W. Larson <larson@mcs.anl.gov> - relocated from
943!           m_AttrVect
944! 15Jan01 - J.W. Larson <larson@mcs.anl.gov> - renamed  GM_scatter_
945!  8Feb01 - J.W. Larson <larson@mcs.anl.gov> - add logic to prevent
946!           empty calls (i.e. no data in buffer) to MPI_SCATTERV()
947! 27Apr01 - R.L. Jacob <jacob@mcs.anl.gov> - small bug fix to
948!           integer attribute scatter
949!  9May01 - J.W. Larson <larson@mcs.anl.gov> - Re-vamped comms model
950!           to reflect MPI comms model for the scatter.  Tidied up
951!           the prologue, too.
952! 18May01 - R.L. Jacob <jacob@mcs.anl.gov> - use MP_Type function
953!           to determine type for mpi_scatterv
954!  8Aug01 - E.T. Ong <eong@mcs.anl.gov> - replace list assignment(=)
955!           with list copy to avoid compiler errors in pgf90.
956! 13Dec01 - E.T. Ong <eong@mcs.anl.gov> - allow scatter with an
957!           AttrVect containing only an iList or rList.
958!EOP ___________________________________________________________________
959
960  character(len=*),parameter :: myname_=myname//'::GM_scatter_'
961  integer :: nIA,nRA,niV,noV,ier
962  integer :: myID
963  integer :: mp_type_Av
964  type(List) :: iList, rList
965  type(AttrVect) :: nonRootAV
966
967  if(present(stat)) stat=0
968
969  call MP_comm_rank(comm,myID,ier)
970  if(ier /= 0) then
971    call MP_perr_die(myname_,'MP_comm_rank()',ier)
972  endif
973
974        ! Verify the input: a _gathered_ vector
975
976  if(myID == root) then
977
978     niV = GlobalMap_gsize(GMap)  ! the _gathered_ local size
979     noV = AttrVect_lsize(iV)     ! the length of the input AttrVect iV
980
981     if(niV /= noV) then
982        write(stderr,'(2a,i5,a,i8,a,i8)') myname_,      &
983             ': myID = ',myID,'.  Invalid input on root, gsize(GMap) =',&
984             niV,', lsize(iV) =',noV
985        if(present(stat)) then
986           stat=-1
987        else
988           call die(myname_)
989        endif
990     endif
991
992  endif
993
994        ! On the root, read the integer and real attribute
995        ! lists off of iV.
996
997  call List_nullify(iList)
998  call List_nullify(rList)
999
1000  if(myID == root) then
1001
1002     ! Count the number of real and integer attributes
1003
1004     nIA = AttrVect_nIAttr(iV)  ! number of INTEGER attributes
1005     nRA = AttrVect_nRAttr(iV)  ! number of REAL attributes
1006
1007     if(nIA > 0) then
1008        call List_copy(iList,iV%iList)
1009     endif
1010
1011     if(nRA > 0) then
1012        call List_copy(rList,iV%rList)
1013     endif
1014
1015  endif
1016 
1017        ! From the root, broadcast iList and rList
1018
1019  call MPI_BCAST(nIA,1,MP_INTEGER,root,comm,ier)
1020  if(ier /= 0) call MP_perr(myname_,'MPI_BCAST(nIA)',ier)
1021
1022  call MPI_BCAST(nRA,1,MP_INTEGER,root,comm,ier)
1023  if(ier /= 0) call MP_perr(myname_,'MPI_BCAST(nRA)',ier)
1024
1025  if(nIA>0) call List_bcast(iList, root, comm)
1026  if(nRA>0) call List_bcast(rList, root, comm)
1027
1028  noV = GlobalMap_lsize(GMap) ! the _scatterd_ local size
1029
1030        ! On all processes, use List data and noV to initialize oV
1031
1032  call AttrVect_init(oV, iList, rList, noV)
1033  call AttrVect_zero(oV)
1034
1035        ! Initialize a dummy AttrVect for non-root MPI calls
1036
1037  if(myID/=root) then
1038    call AttrVect_init(nonRootAV,oV,1)
1039    call AttrVect_zero(nonRootAV)
1040  endif
1041
1042
1043  if(nIA > 0) then
1044
1045     if(myID == root) then
1046
1047        call MPI_scatterv(iV%iAttr(1,1),GMap%counts*nIA,        &
1048             GMap%displs*nIA,MP_INTEGER,oV%iAttr(1,1),          &
1049             noV*nIA,MP_INTEGER,root,comm,ier )
1050        if(ier /= 0) then
1051           call MP_perr_die(myname_,'MPI_scatterv(iAttr) on root',ier)
1052        endif
1053
1054     else
1055
1056        call MPI_scatterv(nonRootAV%iAttr(1,1),GMap%counts*nIA, &
1057             GMap%displs*nIA,MP_INTEGER,oV%iAttr(1,1),          &
1058             noV*nIA,MP_INTEGER,root,comm,ier )
1059        if(ier /= 0) then
1060           call MP_perr_die(myname_,'MPI_scatterv(iAttr) off root',ier)
1061        endif
1062
1063     endif   ! if(myID == root)
1064
1065     call List_clean(iList)
1066
1067  endif   ! if(nIA > 0)
1068
1069  mp_type_Av = MP_Type(1._FP)   ! set mpi type to same as AV%rAttr
1070
1071  if(nRA > 0) then
1072
1073     if(myID == root) then
1074
1075
1076        call MPI_scatterv(iV%rAttr(1,1),GMap%counts*nRA,        &
1077             GMap%displs*nRA,mp_type_Av,oV%rAttr(1,1),          &
1078             noV*nRA,mp_type_Av,root,comm,ier )
1079        if(ier /= 0) then
1080           call MP_perr_die(myname_,'MPI_scatterv(rAttr) on root',ier)
1081        endif
1082
1083     else
1084
1085
1086        call MPI_scatterv(nonRootAV%rAttr,GMap%counts*nRA,      &
1087             GMap%displs*nRA,mp_type_Av,oV%rAttr,          &
1088             noV*nRA,mp_type_Av,root,comm,ier )
1089        if(ier /= 0) then
1090           call MP_perr_die(myname_,'MPI_scatterv(rAttr) off root',ier)
1091        endif
1092
1093     endif
1094
1095     call List_clean(rList)
1096
1097  endif
1098
1099  if(myID /= root) then
1100     call AttrVect_clean(nonRootAV,ier)
1101     if(ier /= 0) then
1102        write(stderr,'(2a,i4)') myname_,        &
1103             ':: AttrVect_clean(nonRootAV) failed for non-root &
1104             &process: myID = ', myID
1105        call die(myname_,':: AttrVect_clean failed &
1106             &for nonRootAV off of root',ier)
1107     endif
1108  endif
1109
1110 end subroutine GM_scatter_
1111
1112!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1113!    Math and Computer Science Division, Argonne National Laboratory   !
1114!BOP -------------------------------------------------------------------
1115!
1116! !IROUTINE: GSM_scatter_ - Scatter an AttrVect using a GlobalSegMap
1117!
1118! !DESCRIPTION:
1119! The routine {\tt GSM\_scatter\_} takes an input {\tt AttrVect} type
1120! {\tt iV} (valid only on the root), and scatters it to a distributed
1121! {\tt AttrVect} {\tt oV}.  The input {\tt GlobalSegMap} argument
1122! {\tt GSMap} dictates how {\tt iV} is scattered to {\tt oV}.  The
1123! success (failure) of this routine is reported in the zero (non-zero)
1124! value of the output argument {\tt stat}.
1125!
1126! {\tt GSM\_scatter\_()} converts the problem of scattering data
1127! according to a {\tt GlobalSegMap} into the simpler problem of
1128! scattering data as specified by a {\tt GlobalMap}.  The {\tt GlobalMap}
1129! variable {\tt GMap} is created based on the local storage requirements
1130! for each distributed piece of {\tt iV}.  On the root, a complete
1131! (including halo points) copy of {\tt iV} is stored in
1132! the temporary {\tt AttrVect} variable {\tt workV} (the length of
1133! {\tt workV} is {\tt GlobalSegMap\_GlobalStorage(GSMap)}).  The
1134! variable {\tt workV} is segmented by process, and segments are
1135! copied into it by process, but ordered in the same order the segments
1136! appear in {\tt GSMap}.  Once {\tt workV} is loaded, the data are
1137! scattered to the output {\tt AttrVect} {\tt oV} by a call to the
1138! routine {\tt GM\_scatter\_()} defined in this module, with {\tt workV}
1139! and {\tt GMap} as the input arguments.
1140!
1141! {\bf N.B.:}  This algorithm  assumes that memory access times are much
1142! shorter than message-passing transmission times.
1143!
1144! {\bf N.B.}:  The output {\tt AttrVect} argument {\tt oV} represents
1145! dynamically allocated memory.  When it is no longer needed, it should
1146! be deallocated by invoking {\tt AttrVect\_clean()} (see the module
1147! {\tt m\_AttrVect} for more details).
1148!
1149! !INTERFACE:
1150
1151 subroutine GSM_scatter_(iV, oV, GSMap, root, comm, stat)
1152!
1153! !USES:
1154!
1155! Environment utilities from mpeu:
1156
1157      use m_stdio
1158      use m_die
1159      use m_mpif90
1160
1161      use m_List, only : List_nullify => nullify
1162
1163! GlobalSegMap and associated services:
1164      use m_GlobalSegMap, only : GlobalSegMap
1165      use m_GlobalSegMap, only : GlobalSegMap_comp_id => comp_id
1166      use m_GlobalSegMap, only : GlobalSegMap_ngseg => ngseg
1167      use m_GlobalSegMap, only : GlobalSegMap_lsize => lsize
1168      use m_GlobalSegMap, only : GlobalSegMap_gsize => gsize
1169      use m_GlobalSegMap, only : GlobalSegMap_GlobalStorage => GlobalStorage
1170! AttrVect and associated services:
1171      use m_AttrVect, only : AttrVect
1172      use m_AttrVect, only : AttrVect_init => init
1173      use m_AttrVect, only : AttrVect_zero => zero
1174      use m_AttrVect,  only : AttrVect_lsize => lsize
1175      use m_AttrVect, only : AttrVect_nIAttr => nIAttr
1176      use m_AttrVect, only : AttrVect_nRAttr => nRAttr
1177      use m_AttrVect, only : AttrVect_clean => clean 
1178! GlobalMap and associated services:
1179      use m_GlobalMap, only : GlobalMap
1180      use m_GlobalMap, only : GlobalMap_init => init
1181      use m_GlobalMap, only : GlobalMap_clean => clean
1182
1183      implicit none
1184
1185! !INPUT PARAMETERS:
1186!
1187      type(AttrVect),            intent(in)  :: iV
1188      type(GlobalSegMap),        intent(in)  :: GSMap
1189      integer,                   intent(in)  :: root
1190      integer,                   intent(in)  :: comm
1191
1192! !OUTPUT PARAMETERS:
1193!
1194      type(AttrVect),            intent(out) :: oV
1195      integer,        optional,  intent(out) :: stat
1196
1197! !REVISION HISTORY:
1198! 15Jan01 - J.W. Larson <larson@mcs.anl.gov> - API specification.
1199!  8Feb01 - J.W. Larson <larson@mcs.anl.gov> - Initial code.
1200! 25Feb01 - J.W. Larson <larson@mcs.anl.gov> - Bug fix--replaced
1201!           call to GlobalSegMap_lsize with call to the new fcn.
1202!           GlobalSegMap_ProcessStorage().
1203! 26Apr01 - R.L. Jacob <jacob@mcs.anl.gov> - add use statement for
1204!           AttVect_clean
1205! 26Apr01 - J.W. Larson <larson@mcs.anl.gov> - bug fixes--data
1206!           misalignment in use of the GlobalMap to compute the
1207!           memory map into workV, and initialization of workV
1208!           on all processes.
1209!  9May01 - J.W. Larson <larson@mcs.anl.gov> - tidied up prologue
1210! 15May01 - Larson / Jacob <larson@mcs.anl.gov> - stopped initializing
1211!           workV on off-root processes (no longer necessary).
1212! 13Jun01 - J.W. Larson <larson@mcs.anl.gov> - Initialize stat
1213!           (if present).
1214! 20Jun01 - J.W. Larson <larson@mcs.anl.gov> - Fixed a subtle bug
1215!           appearing on AIX regarding the fact workV is uninitial-
1216!           ized on non-root processes.  This is fixed by nullifying
1217!           all the pointers in workV for non-root processes.
1218! 20Aug01 - E.T. Ong <eong@mcs.anl.gov> - Added argument check
1219!           for matching processors in gsmap and comm.
1220! 13Dec01 - E.T. Ong <eong@mcs.anl.gov> - got rid of restriction
1221!           GlobalStorage(GSMap)==AttrVect_lsize(AV) to allow for
1222!           GSMap to be haloed.
1223! 11Aug08 - R. Jacob <jacob@mcs.anl.gov> - remove call to ProcessStorage
1224!           and replace with faster algorithm provided by Pat Worley
1225!EOP ___________________________________________________________________
1226
1227  character(len=*),parameter :: myname_=myname//'::GSM_scatter_'
1228
1229! Temporary workspace AttrVect:
1230  type(AttrVect) :: workV
1231! Component ID and number of segments for GSMap:
1232  integer :: comp_id, ngseg, iseg
1233! Total length of GSMap segments laid end-to-end:
1234  integer :: global_storage
1235! Error Flag
1236  integer :: ierr
1237! Number of processes on communicator, and local rank:
1238  integer :: NumProcs, myID
1239! Total local storage on each pe according to GSMap:
1240  integer, dimension(:), allocatable :: lns
1241! Temporary GlobalMap used to scatter the segmented (by pe) data
1242  type(GlobalMap) :: GMap
1243! Loop counters and temporary indices:
1244  integer :: m, n, ilb, iub, olb, oub, pe
1245! workV segment tracking index array:
1246  integer, dimension(:), allocatable :: current_pos
1247
1248      ! Initialize stat (if present)
1249
1250  if(present(stat)) stat = 0
1251
1252       ! Which process am I?
1253
1254  call MPI_COMM_RANK(comm, myID, ierr)
1255
1256  if(ierr /= 0) then
1257     call MP_perr_die(myname_,'MPI_COMM_RANK',ierr)
1258  endif
1259
1260  if(myID == root) then
1261     
1262     if(GSMap%gsize > AttrVect_lsize(iV)) then
1263        write(stderr,'(2a,i5,a,i8,a,i8)') myname_,      &
1264             ': myID = ',myID,'.  Invalid input, GSMap%gsize =',&
1265             GSMap%gsize, ', lsize(iV) =',AttrVect_lsize(iV)
1266        if(present(stat)) then
1267           stat=-1
1268        else
1269           call die(myname_)
1270        endif
1271     endif
1272
1273  endif     
1274
1275       ! On the root, initialize a work AttrVect type of the
1276       ! above length, and with the same attribute lists as iV.
1277       ! on other processes, initialize workV only with the
1278       ! attribute information, but no storage.
1279
1280  if(myID == root) then
1281
1282     global_storage = GlobalSegMap_GlobalStorage(GSMap)
1283     call AttrVect_init(workV, iV, global_storage)
1284     call AttrVect_zero(workV)
1285
1286  else
1287       ! nullify workV just to be safe
1288 
1289     call List_nullify(workV%iList)
1290     call List_nullify(workV%rList)
1291     nullify(workV%iAttr)
1292     nullify(workV%rAttr)
1293
1294  endif
1295
1296       ! Return to processing on the root to load workV:
1297
1298       ! How many processes are there on this communicator?
1299
1300  call MPI_COMM_SIZE(comm, NumProcs, ierr)
1301
1302  if(ierr /= 0) then
1303     call MP_perr_die(myname_,'MPI_COMM_SIZE',ierr)
1304  endif
1305
1306       ! Processor Check: Do the processors on GSMap match those in comm?
1307
1308  if(MAXVAL(GSMap%pe_loc) > (NumProcs-1)) then
1309     write(stderr,*) myname_, &
1310          ":: Procs in GSMap%pe_loc do not match procs in communicator ", &
1311          NumProcs-1, MAXVAL(GSMap%pe_loc)
1312     if(present(stat)) then
1313        stat=1
1314        return
1315     else
1316        call die(myname_)
1317     endif
1318  endif
1319
1320  if(myID == root) then
1321
1322       ! Allocate a precursor to a GlobalMap accordingly...
1323
1324     allocate(lns(0:NumProcs-1), stat=ierr)
1325     if(ierr /= 0) then
1326        write(stderr,*) myname_,':: allocate(lns...) failed, stat=',ierr
1327        if(present(stat)) then
1328           stat=ierr
1329        else
1330           call die(myname_,'allocate(lns)',ierr)
1331        endif
1332     endif
1333
1334       ! And Load it...
1335
1336     lns(:)=0
1337     do iseg=1,GSMap%ngseg
1338        n = GSMap%pe_loc(iseg)
1339        lns(n) = lns(n) + GSMap%length(iseg)
1340     end do
1341
1342  endif ! if(myID == root)
1343
1344        ! Non-root processes call GlobalMap_init with lns,
1345        ! although this argument is not used in the
1346        ! subroutine. Since it correspond to a dummy shaped array arguments
1347        ! in GlobslMap_init, the Fortran 90 standard dictates that the actual
1348        ! argument must contain complete shape information. Therefore,
1349        ! the array argument must be allocated on all processes.
1350
1351  if(myID /= root) then
1352
1353     allocate(lns(1),stat=ierr)
1354     if(ierr /= 0) then
1355        write(stderr,*) myname_,':: allocate(lns...) failed, stat=',ierr
1356        if(present(stat)) then
1357           stat=ierr
1358           return
1359        else
1360           call die(myname_,'allocate(lns(1))',ierr)
1361        endif
1362     endif
1363
1364  endif ! if(myID /= root)...
1365
1366       ! Create a GlobalMap describing the 1-D decomposition
1367       ! of workV:
1368
1369  comp_id = GlobalSegMap_comp_id(GSMap)
1370
1371  call GlobalMap_init(GMap, comp_id, lns, root, comm)
1372
1373       ! On the root, load workV:
1374
1375  if(myID == root) then
1376
1377       ! On the root, allocate current position index for
1378       ! each process chunk:
1379
1380     allocate(current_pos(0:NumProcs-1), stat=ierr)
1381     if(ierr /= 0) then
1382        write(stderr,*) myname_,':: allocate(current_pos..) failed, stat=', &
1383             ierr
1384        if(present(stat)) then
1385           stat=ierr
1386           return
1387        else
1388           call die(myname_,'allocate(current_pos)',ierr)
1389        endif
1390     endif
1391
1392       ! Initialize current_pos(:) using GMap%displs(:)
1393
1394     do n=0,NumProcs-1
1395        current_pos(n) = GMap%displs(n) + 1
1396     end do
1397
1398       ! Load each segment of iV into its appropriate segment
1399       ! of workV:
1400
1401     ngseg = GlobalSegMap_ngseg(GSMap)
1402
1403     do n=1,ngseg
1404
1405       ! Determine which process owns segment n:
1406
1407        pe = GSMap%pe_loc(n)
1408
1409       ! Input map (lower/upper indicess) of segment of iV:
1410
1411        ilb = GSMap%start(n)
1412        iub = GSMap%start(n) + GSMap%length(n) - 1
1413
1414       ! Output map of (lower/upper indicess) segment of workV:
1415
1416        olb = current_pos(pe)
1417        oub = current_pos(pe) + GSMap%length(n) - 1
1418
1419       ! Increment current_pos(n) for next time:
1420
1421        current_pos(pe) = current_pos(pe) + GSMap%length(n)
1422
1423       ! Now we are equipped to do the copy:
1424
1425        do m=1,AttrVect_nIAttr(iV)
1426           workV%iAttr(m,olb:oub) = iV%iAttr(m,ilb:iub)
1427        end do
1428
1429        do m=1,AttrVect_nRAttr(iV)
1430           workV%rAttr(m,olb:oub) = iV%rAttr(m,ilb:iub)
1431        end do
1432
1433     end do ! do n=1,ngseg
1434
1435       ! Clean up current_pos, which was only allocated on the root
1436
1437     deallocate(current_pos, stat=ierr)
1438     if(ierr /= 0) then
1439        write(stderr,*) myname_,':: deallocate(current_pos) failed.  ', &
1440             'stat = ',ierr
1441        if(present(stat)) then
1442           stat=ierr
1443           return
1444        else
1445           call die(myname_,'deallocate(current_pos)',ierr)
1446        endif
1447     endif
1448
1449  endif ! if(myID == root)
1450
1451       ! Now we are in business...we have:  1) an AttrVect laid out
1452       ! in contiguous segments, each segment corresponding to a
1453       ! process, and in the same order dictated by GSMap;
1454       ! 2) a GlobalMap telling us which segment of workV goes to
1455       ! which process.  Thus, we can us GM_scatter_() to achieve
1456       ! our goal.
1457
1458  call GM_scatter_(workV, oV, GMap, root, comm, ierr)
1459  if(ierr /= 0) then
1460     write(stderr,*) myname,':: ERROR in return from GM_scatter_(), ierr=',&
1461          ierr
1462     if(present(stat)) then
1463        stat = ierr
1464        return
1465     else
1466        call die(myname_,'ERROR returning from GM_scatter_()',ierr)
1467     endif
1468  endif
1469
1470       ! Finally, clean up allocated structures:
1471 
1472  if(myID == root) then
1473     call AttrVect_clean(workV)
1474  endif
1475
1476  call GlobalMap_clean(GMap)
1477
1478  deallocate(lns, stat=ierr)
1479  if(ierr /= 0) then
1480     write(stderr,*) myname_,':: ERROR in deallocate(lns), ierr=',ierr
1481     if(present(stat)) then
1482        stat=ierr
1483        return
1484     else
1485        call die(myname_,'deallocate(lns)',ierr)
1486     endif
1487  endif
1488
1489 end subroutine GSM_scatter_
1490
1491!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1492!    Math and Computer Science Division, Argonne National Laboratory   !
1493!BOP -------------------------------------------------------------------
1494!
1495! !IROUTINE: bcast_ - Broadcast an AttrVect
1496!
1497! !DESCRIPTION:  This routine takes an {\tt AttrVect} argument {\tt aV}
1498! (at input, valid on the root only), and broadcasts it to all the
1499! processes associated with the communicator handle {\tt comm}.  The
1500! success (failure) of this routine is reported in the zero (non-zero)
1501! value of the output argument {\tt stat}.
1502!
1503! {\bf N.B.}:  The output (on non-root processes) {\tt AttrVect} argument
1504! {\tt aV} represents dynamically allocated memory.  When it is no longer
1505! needed, it should be deallocated by invoking {\tt AttrVect\_clean()}
1506! (see the module {\tt m\_AttrVect} for details).
1507!
1508! !INTERFACE:
1509
1510 subroutine bcast_(aV, root, comm, stat)
1511!
1512! !USES:
1513!
1514      use m_stdio
1515      use m_die
1516      use m_mpif90
1517      use m_String, only : String,bcast,char,String_clean
1518      use m_String, only : String_bcast => bcast
1519      use m_List, only : List_get => get
1520      use m_AttrVect, only : AttrVect
1521      use m_AttrVect, only : AttrVect_init => init
1522      use m_AttrVect, only : AttrVect_zero => zero
1523      use m_AttrVect, only : AttrVect_lsize => lsize
1524      use m_AttrVect, only : AttrVect_nIAttr => nIAttr
1525      use m_AttrVect, only : AttrVect_nRAttr => nRAttr
1526
1527      implicit none
1528
1529! !INPUT PARAMETERS:
1530!
1531      integer,                  intent(in)    :: root
1532      integer,                  intent(in)    :: comm
1533
1534! !INPUT/OUTPUT PARAMETERS:
1535!
1536      type(AttrVect),           intent(inout) :: aV ! (IN) on the root,
1537                                                    ! (OUT) elsewhere
1538
1539! !OUTPUT PARAMETERS:
1540!
1541      integer,        optional, intent(out)   :: stat
1542
1543! !REVISION HISTORY:
1544! 27Apr98 - Jing Guo <guo@thunder> - initial prototype/prologue/code
1545! 27Oct00 - J.W. Larson <larson@mcs.anl.gov> - relocated from
1546!           m_AttrVect
1547!  9May01 - J.W. Larson <larson@mcs.anl.gov> - tidied up prologue
1548! 18May01 - R.L. Jacob <jacob@mcs.anl.gov> - use MP_Type function
1549!           to determine type for bcast
1550! 19Dec01 - E.T. Ong <eong@mcs.anl.gov> - adjusted for case of AV with
1551!           only integer or real attribute
1552!EOP ___________________________________________________________________
1553
1554  character(len=*),parameter :: myname_=myname//'::bcast_'
1555  type(String) :: iLStr,rLStr
1556  integer :: nIA, nRA, lsize
1557  integer :: myID
1558  integer :: ier
1559  integer :: mp_Type_aV
1560
1561  if(present(stat)) stat=0
1562
1563  call MP_comm_rank(comm,myID,ier)
1564  if(ier /= 0) then
1565    call MP_perr_die(myname_,'MP_comm_rank()',ier)
1566  endif
1567
1568       ! Broadcaast to all PEs
1569
1570  if(myID == root) then
1571     nIA = AttrVect_nIAttr(aV)
1572     nRA = AttrVect_nRAttr(aV)
1573     lsize = AttrVect_lsize(aV)
1574  endif
1575
1576  call MPI_bcast(nIA,1,MP_INTEGER,root,comm,ier)
1577  if(ier /= 0) then
1578    call MP_perr_die(myname_,'MPI_bcast(nIA)',ier)
1579  endif
1580
1581  call MPI_bcast(nRA,1,MP_INTEGER,root,comm,ier)
1582  if(ier /= 0) then
1583    call MP_perr_die(myname_,'MPI_bcast(nRA)',ier)
1584  endif
1585
1586  call MPI_bcast(lsize,1,MP_INTEGER,root,comm,ier)
1587  if(ier /= 0) then
1588    call MP_perr_die(myname_,'MPI_bcast(lsize)',ier)
1589  endif
1590
1591        ! Convert the two Lists to two Strings
1592
1593  if(nIA>0) then
1594
1595     if(myID == root) call List_get(iLStr,aV%iList)
1596
1597     call String_bcast(iLStr,root,comm,stat=ier)        ! bcast.String()
1598
1599     if(ier /= 0) then
1600        write(stderr,*) myname_,'bcast.String(iLstr), ier=',ier
1601        if(present(stat)) then
1602           stat=ier
1603           return
1604        else
1605           call die(myname_,'String_bcast(iLStr) failed',ier)
1606        endif
1607     endif ! if(ier /= 0)...
1608
1609  endif ! if(nIA > 0)...
1610
1611
1612  if(nRA>0) then
1613
1614     if(myID == root) call List_get(rLStr,aV%rList)
1615
1616     call String_bcast(rLStr,root,comm,stat=ier)        ! bcast.String()
1617     if(ier /= 0) then
1618        write(stderr,*) myname_,'bcast.String(iLstr), ier=',ier
1619        if(present(stat)) then
1620           stat=ier
1621           return
1622        else
1623           call die(myname_,'String_bcast(iLStr) failed',ier)
1624        endif
1625     endif ! if(ier /= 0)...
1626
1627  endif ! if(nRA > 0)...
1628
1629  if(myID /= root) then
1630     
1631     if( (nIA>0) .and. (nRA>0) ) then
1632        call AttrVect_init(aV,iList=char(iLStr),rList=char(rLStr), &
1633                           lsize=lsize)
1634     endif
1635
1636     if( (nIA>0) .and. (nRA<=0) ) then
1637        call AttrVect_init(aV,iList=char(iLStr),lsize=lsize)
1638     endif
1639
1640     if( (nIA<=0) .and. (nRA>0) ) then
1641        call AttrVect_init(aV,rList=char(rLStr),lsize=lsize)
1642     endif
1643
1644     if( (nIA<=0) .and. (nRA<=0) ) then
1645        write(stderr,*) myname_,':: Nonpositive numbers of both ',&
1646             'real AND integer attributes.  nIA =',nIA,' nRA=',nRA
1647        if(present(stat)) then
1648           stat = -1
1649           return
1650        else
1651           call die(myname_,'AV has not been initialized',-1)
1652        endif
1653     endif ! if((nIA<= 0) .and. (nRA<=0))...
1654
1655     call AttrVect_zero(aV)
1656
1657
1658  endif ! if(myID /= root)...
1659
1660  if(nIA > 0) then
1661
1662     mp_Type_aV=MP_Type(av%iAttr)
1663     call MPI_bcast(aV%iAttr,nIA*lsize,mp_Type_aV,root,comm,ier)
1664     if(ier /= 0) then
1665        call MP_perr_die(myname_,'MPI_bcast(iAttr) failed.',ier)
1666     endif
1667
1668     call String_clean(iLStr)
1669
1670  endif
1671
1672  if(nRA > 0) then
1673
1674     mp_Type_aV=MP_Type(av%rAttr)
1675     call MPI_bcast(aV%rAttr,nRA*lsize,mp_Type_aV,root,comm,ier)
1676     if(ier /= 0) then
1677        call MP_perr_die(myname_,'MPI_bcast(rAttr) failed.',ier)
1678     endif
1679
1680     call String_clean(rLStr)
1681
1682  endif
1683
1684 end subroutine bcast_
1685
1686 end module m_AttrVectComms
1687
1688
1689
Note: See TracBrowser for help on using the repository browser.