source: CPL/oasis3-mct/branches/OASIS3-MCT_2.0_branch/lib/mct/mct/m_MCTWorld.F90 @ 4775

Last change on this file since 4775 was 4775, checked in by aclsce, 4 years ago
  • Imported oasis3-mct from Cerfacs svn server (not suppotred anymore).

The version has been extracted from https://oasis3mct.cerfacs.fr/svn/branches/OASIS3-MCT_2.0_branch/oasis3-mct@1818

File size: 27.0 KB
Line 
1!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2!    Math and Computer Science Division, Argonne National Laboratory   !
3!-----------------------------------------------------------------------
4! CVS m_MCTWorld.F90,v 1.26 2007/06/01 19:56:25 rloy Exp
5! CVS MCT_2_4_0
6!BOP -------------------------------------------------------------------
7!
8! !MODULE: m_MCTWorld -- MCTWorld Class
9!
10! !DESCRIPTION:
11! MCTWorld is a datatype which acts as a component model registry.
12! All models communicating through MCT must participate in initialization
13! of MCTWorld.  The single instance of MCTWorld, {\tt ThisMCTWorld} stores
14! the component id and local and global processor rank of each component.
15! This module contains methods for creating and destroying {\tt ThisMCTWorld}
16! as well as inquiry functions.
17!
18! !INTERFACE:
19
20 module m_MCTWorld
21!
22! !USES:
23      use m_List, only : List   ! Support for List components.
24
25      implicit none
26
27      private   ! except
28
29! !PUBLIC TYPES:
30
31      public :: MCTWorld        ! The MCTWorld  class data structure
32
33    type MCTWorld
34      integer :: MCT_comm                          ! MCT communicator
35      integer :: ncomps                            ! Total number of components
36      integer :: mygrank                           ! Rank of this processor in
37                                                   ! global communicator.
38      integer,dimension(:),pointer :: nprocspid    ! Number of processes
39                                                   ! each component is on (e.g. rank of its
40                                                   ! local communicator.
41      integer,dimension(:,:),pointer :: idGprocid  ! Translate between local component rank
42                                                   ! rank in global communicator.
43                                                   ! idGprocid(modelid,localrank)=globalrank
44    end type MCTWorld
45
46! !PUBLIC DATA MEMBERS:
47
48    type(MCTWorld) :: ThisMCTWorld   !  declare the MCTWorld
49
50! !PUBLIC MEMBER FUNCTIONS:
51      public :: initialized          ! Determine if MCT is initialized
52      public :: init                 ! Create a MCTWorld
53      public :: clean                ! Destroy a MCTWorld
54      public :: NumComponents        ! Number of Components in the MCTWorld
55      public :: ComponentNumProcs    ! Number of processes owned by a given
56                                     ! component
57      public :: ComponentToWorldRank ! Given the rank of a process on a
58                                     ! component, return its rank on the
59                                     ! world communicator
60      public :: ComponentRootRank    ! Return the rank on the world
61                                     ! communicator of the root process of
62                                     ! a component
63      public :: ThisMCTWorld         ! Instantiation of the MCTWorld
64
65
66
67    interface initialized ; module procedure &
68      initialized_
69    end interface
70    interface init ; module procedure &
71      initd_, &
72      initm_, &
73      initr_
74    end interface
75    interface clean ; module procedure clean_ ; end interface
76    interface NumComponents ; module procedure &
77       NumComponents_ 
78    end interface
79    interface ComponentNumProcs ; module procedure &
80       ComponentNumProcs_ 
81    end interface
82    interface ComponentToWorldRank ; module procedure &
83       ComponentToWorldRank_ 
84    end interface
85    interface ComponentRootRank ; module procedure &
86       ComponentRootRank_ 
87    end interface
88
89
90
91! !REVISION HISTORY:
92! 19Jan01 - R. Jacob <jacob@mcs.anl.gov> - initial prototype
93! 05Feb01 - J. Larson <larson@mcs.anl.gov> - added query and
94!           local-to-global mapping services NumComponents,
95!           ComponentNumProcs, ComponentToWorldRank, and ComponentRootRank
96! 08Feb01 - R. Jacob <jacob@mcs.anl.gov> - add mylrank and mygrank
97!           to datatype
98! 20Apr01 - R. Jacob <jacob@mcs.anl.gov> - remove allids from
99!           MCTWorld datatype.  Not needed because component
100!           ids are always from 1 to number-of-components.
101! 07Jun01 - R. Jacob <jacob@mcs.anl.gov> - remove myid, mynprocs
102!           and mylrank from MCTWorld datatype because they are not
103!           clearly defined in PCM mode.  Add MCT_comm for future use.
104! 03Aug01 - E. Ong <eong@mcs.anl.gov> - explicity specify starting
105!           address in mpi_irecv
106! 27Nov01 - E. Ong <eong@mcs.anl.gov> - added R. Jacob's version of initd_
107!           to support PCM mode.
108! 15Feb02 - R. Jacob - elminate use of MP_COMM_WORLD.  Use
109!           argument globalcomm instead.  Create MCT_comm from
110!           globalcomm
111!EOP __________________________________________________________________
112
113  character(len=*),parameter :: myname='MCT::m_MCTWorld'
114
115 contains
116
117
118
119!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
120!    Math and Computer Science Division, Argonne National Laboratory   !
121!BOP -------------------------------------------------------------------
122!
123! !IROUTINE: initialized_ - determine if MCTWorld is initialized
124!
125! !DESCRIPTION:
126! This routine may be used to determine whether {\tt MCTWorld::init}
127! has been called.  If not, the user must call {\tt init} before
128! performing any other MCT library calls.
129!
130! !INTERFACE:
131
132 logical function initialized_()
133
134!
135! !USES:
136!
137
138! !INPUT PARAMETERS:
139
140
141! !REVISION HISTORY:
142! 01June07 - R. Loy <rloy@mcs.anl.gov> - initial version
143!EOP ___________________________________________________________________
144!
145
146  initialized_ = associated(ThisMCTWorld%nprocspid)
147
148  end function initialized_
149
150
151
152
153!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
154!    Math and Computer Science Division, Argonne National Laboratory   !
155!BOP -------------------------------------------------------------------
156!
157! !IROUTINE: initm_ - initialize MCTWorld
158!
159! !DESCRIPTION:
160! Do a distributed init of MCTWorld for the case where a set of processors
161! contains more then one model and the models may not span the set of processors.
162! {\tt ncomps} is the total number of components in the entire coupled system.
163! {\tt globalcomm} encompasses all the models (typically this can be MPI\_COMM\_WORLD).
164! {\tt mycomms} is an array of MPI communicators, each sized for the appropriate model
165! and {\tt myids} is a corresponding array of integers containing the model ids for
166! the models on this particular set of processors.
167!
168! This routine is called once for the models covered by the set of processors.
169!
170! !INTERFACE:
171
172 subroutine initm_(ncomps,globalcomm,mycomms,myids)
173!
174! !USES:
175!
176      use m_mpif90
177      use m_die
178      use m_stdio
179
180      implicit none
181
182! !INPUT PARAMETERS:
183
184      integer, intent(in)              :: ncomps          ! number of components
185      integer, intent(in)              :: globalcomm      ! global communicator
186      integer, dimension(:),pointer    :: mycomms         ! my communicators
187      integer, dimension(:),pointer    :: myids           ! component ids
188
189! !REVISION HISTORY:
190! 20Sep07 - T. Craig migrated code from initd routine
191! 20Sep07 - T. Craig - made mycomms an array
192!EOP ___________________________________________________________________
193!
194  character(len=*),parameter :: myname_=myname//'::initm_'
195  integer :: ier,myGid,myLid,i,mysize,Gsize,j
196
197! arrays allocated on the root to coordinate gathring of data
198! and non-blocking receives by the root
199  integer, dimension(:), allocatable :: compids,reqs,nprocs,Gprocids
200  integer, dimension(:), allocatable :: root_nprocs
201  integer, dimension(:,:),allocatable :: status,root_idGprocid
202  integer, dimension(:,:),pointer :: tmparray
203  integer,dimension(:),pointer :: apoint
204! ------------------------------------------------------------------
205
206! Check that ncomps is a legal value
207  if(ncomps < 1) then
208     call die(myname_, "argument ncomps can't less than one!",ncomps)
209  endif
210
211  if (size(myids) /= size(mycomms)) then
212     call die(myname_, "size of myids and mycomms inconsistent")
213  endif
214
215! make sure this has not been called already
216  if(associated(ThisMCTWorld%nprocspid) ) then
217     write(stderr,'(2a)') myname_, &
218      'MCTERROR:  MCTWorld has already been initialized...Continuing'
219       RETURN
220  endif
221
222! determine overall size
223  call MP_comm_size(globalcomm,Gsize,ier)
224  if(ier /= 0) call MP_perr_die(myname_,'MP_comm_size()',ier)
225
226! determine my rank in comm_world
227  call MP_comm_rank(globalcomm,myGid,ier)
228  if(ier /= 0) call MP_perr_die(myname_,'MP_comm_rank()',ier)
229
230! allocate space on global root to receive info about
231! the other components
232  if(myGid == 0) then
233     allocate(nprocs(ncomps),compids(ncomps),&
234     reqs(ncomps),status(MP_STATUS_SIZE,ncomps),&
235     root_nprocs(ncomps),stat=ier)
236     if (ier /= 0) then
237        call die(myname_, 'allocate(nprocs,...)',ier)
238     endif
239  endif
240
241
242!!!!!!!!!!!!!!!!!!
243!  Gather the number of procs from the root of each component
244!!!!!!!!!!!!!!!!!!
245!
246!  First on the global root, post a receive for each component
247  if(myGid == 0) then
248    do i=1,ncomps
249       call MPI_IRECV(root_nprocs(i), 1, MP_INTEGER, MP_ANY_SOURCE,i, &
250         globalcomm, reqs(i), ier)
251       if(ier /= 0) call MP_perr_die(myname_,'MPI_IRECV(root_nprocs)',ier)
252    enddo
253  endif
254
255!  The local root on each component sends
256  do i=1,size(myids)
257    if(mycomms(i)/=MP_COMM_NULL) then
258      call MP_comm_size(mycomms(i),mysize,ier)
259      if(ier /= 0) call MP_perr_die(myname_,'MP_comm_size()',ier)
260      call MP_comm_rank(mycomms(i),myLid,ier)
261      if(ier /= 0) call MP_perr_die(myname_,'MP_comm_rank()',ier)
262      if(myLid == 0) then
263        call MPI_SEND(mysize,1,MP_INTEGER,0,myids(i),globalcomm,ier)
264        if(ier /= 0) call MP_perr_die(myname_,'MPI_SEND(mysize)',ier)
265      endif
266    endif
267  enddo
268
269!  Global root waits for all sends
270  if(myGid == 0) then
271    call MPI_WAITALL(size(reqs), reqs, status, ier)
272    if(ier /= 0) call MP_perr_die(myname_,'MPI_WAITALL()',ier)
273  endif
274! Global root now knows how many processors each component is using
275
276!!!!!!!!!!!!!!!!!!
277! end of nprocs
278!!!!!!!!!!!!!!!!!!
279
280
281! allocate a tmp array for the receive on root.
282  if(myGid == 0) then
283    allocate(tmparray(0:Gsize-1,ncomps),stat=ier)
284    if(ier/=0) call die(myname_,'allocate(tmparray)',ier)
285
286! fill tmparray with a bad rank value for later error checking
287    tmparray = -1
288  endif
289
290!!!!!!!!!!!!!!!!!!
291!  Gather the Gprocids from each local root
292!!!!!!!!!!!!!!!!!!
293!
294!  First on the global root, post a receive for each component
295  if(myGid == 0) then
296    do i=1,ncomps
297       apoint => tmparray(0:Gsize-1,i)
298       call MPI_IRECV(apoint(1), root_nprocs(i),MP_INTEGER, &
299       MP_ANY_SOURCE,i,globalcomm, reqs(i), ier)
300       if(ier /= 0) call MP_perr_die(myname_,'MPI_IRECV()',ier)
301    enddo
302  endif
303
304!  The root on each component sends
305  do i=1,size(myids)
306    if(mycomms(i)/=MP_COMM_NULL) then
307      call MP_comm_size(mycomms(i),mysize,ier)
308      if(ier /= 0) call MP_perr_die(myname_,'MP_comm_size()',ier)
309      call MP_comm_rank(mycomms(i),myLid,ier)
310      if(ier /= 0) call MP_perr_die(myname_,'MP_comm_rank()',ier)
311
312! make the master list of global proc ids
313!
314! allocate space to hold global ids
315! only needed on root, but allocate everywhere to avoid complaints.
316      allocate(Gprocids(mysize),stat=ier)
317      if(ier/=0) call die(myname_,'allocate(Gprocids)',ier)
318! gather over the LOCAL comm
319      call MPI_GATHER(myGid,1,MP_INTEGER,Gprocids,1,MP_INTEGER,0,mycomms(i),ier)
320      if(ier/=0) call die(myname_,'MPI_GATHER Gprocids',ier)
321
322      if(myLid == 0) then
323        call MPI_SEND(Gprocids,mysize,MP_INTEGER,0,myids(i),globalcomm,ier)
324        if(ier /= 0) call MP_perr_die(myname_,'MPI_SEND(Gprocids)',ier)
325      endif
326
327      deallocate(Gprocids,stat=ier)
328      if(ier/=0) call die(myname_,'deallocate(Gprocids)',ier)
329    endif
330  enddo
331
332!  Global root waits for all sends
333  if(myGid == 0) then
334    call MPI_WAITALL(size(reqs), reqs, status, ier)
335    if(ier /= 0) call MP_perr_die(myname_,'MPI_WAITALL(Gprocids)',ier)
336  endif
337
338!  Now store the Gprocids in the World description and Broadcast
339
340  if(myGid == 0) then
341    allocate(root_idGprocid(ncomps,0:Gsize-1),stat=ier)
342    if(ier/=0) call die(myname_,'allocate(root_idGprocid)',ier)
343
344    root_idGprocid = transpose(tmparray)
345  endif
346
347  if(myGid /= 0) then
348     allocate(root_nprocs(1),root_idGprocid(1,1),stat=ier)
349     if(ier/=0) call die(myname_,'non-root allocate(root_idGprocid)',ier)
350  endif
351
352!!!!!!!!!!!!!!!!!!
353! end of Gprocids
354!!!!!!!!!!!!!!!!!!
355
356! now call the init from root.
357  call initr_(ncomps,globalcomm,root_nprocs,root_idGprocid)
358
359! if(myGid==0 .or. myGid==17) then
360!   write(*,*)'MCTA',myGid,ThisMCTWorld%ncomps,ThisMCTWorld%MCT_comm,ThisMCTWorld%nprocspid
361!   do i=1,ThisMCTWorld%ncomps
362!     write(*,*)'MCTK',myGid,i,ThisMCTWorld%idGprocid(i,0:ThisMCTWorld%nprocspid(i)-1)
363!   enddo
364! endif
365
366! deallocate temporary arrays
367 deallocate(root_nprocs,root_idGprocid,stat=ier)
368 if(ier/=0) call die(myname_,'deallocate(root_nprocs,..)',ier)
369 if(myGid == 0) then
370   deallocate(compids,reqs,status,nprocs,tmparray,stat=ier)
371   if(ier/=0) call die(myname_,'deallocate(compids,..)',ier)
372 endif
373
374 end subroutine initm_
375
376!BOP -------------------------------------------------------------------
377!
378! !IROUTINE: initd_ - initialize MCTWorld
379!
380! !DESCRIPTION:
381! Do a distributed init of MCTWorld using the total number of components
382! {\tt ncomps} and either a unique integer component id {\tt myid} or,
383! if more than one model is placed on a processor, an array of integer ids
384! specifying the models {\tt myids}.  Also required is
385! the local communicator {\tt mycomm} and global communicator {\tt globalcomm}
386! which encompasses all the models (typically this can be MPI\_COMM\_WORLD).
387! This routine must be called once by each component (using {\em myid}) or
388! component group (using {\em myids}).
389!
390! !INTERFACE:
391
392 subroutine initd_(ncomps,globalcomm,mycomm,myid,myids)
393!
394! !USES:
395!
396      use m_mpif90
397      use m_die
398      use m_stdio
399
400      implicit none
401
402! !INPUT PARAMETERS:
403
404      integer, intent(in)              :: ncomps          ! number of components
405      integer, intent(in)              :: globalcomm      ! global communicator
406      integer, intent(in)              :: mycomm          ! my communicator
407      integer, intent(in),optional     :: myid            ! my component id
408      integer, dimension(:),pointer,optional  :: myids    ! component ids
409
410! !REVISION HISTORY:
411! 19Jan01 - R. Jacob <jacob@mcs.anl.gov> - initial prototype
412! 07Feb01 - R. Jacob <jacob@mcs.anl.gov> - non fatal error
413!           if init is called a second time.
414! 08Feb01 - R. Jacob <jacob@mcs.anl.gov> - initialize the new
415!           mygrank and mylrank
416! 20Apr01 - R. Jacob <jacob@mcs.anl.gov> - remove allids from
417!           MCTWorld datatype.  Not needed because component
418!           ids are always from 1 to number-of-components.
419! 22Jun01 - R. Jacob <jacob@mcs.anl.gov> - move Bcast and init
420!           of MCTWorld to initr_
421! 20Sep07 - T. Craig migrated code to new initm routine
422!EOP ___________________________________________________________________
423!
424  character(len=*),parameter :: myname_=myname//'::initd_'
425  integer :: msize,ier
426  integer, dimension(:), pointer :: mycomm1d,myids1d
427
428! ------------------------------------------------------------------
429
430
431! only one of myid and myids should be present
432  if(present(myid) .and. present(myids)) then
433    write(stderr,'(2a)') myname_, &
434      'MCTERROR:  Must define myid or myids in MCTWord init'
435      call die(myname_)
436  endif
437
438  if(.not.present(myid) .and. .not.present(myids)) then
439    write(stderr,'(2a)') myname_, &
440      'MCTERROR:  Must define one of myid or myids in MCTWord init'
441      call die(myname_)
442  endif
443
444  if (present(myids)) then
445     msize = size(myids)
446  else
447     msize = 1
448  endif
449
450  allocate(mycomm1d(msize),myids1d(msize),stat=ier)
451  if(ier/=0) call die(myname_,'non-root allocate(root_idGprocid)',ier)
452  mycomm1d(:) = mycomm
453
454  if (present(myids)) then
455     myids1d(:) = myids(:)
456  else
457     myids1d(:) = myid
458  endif
459
460  call initm_(ncomps,globalcomm,mycomm1d,myids1d)
461
462  deallocate(mycomm1d,myids1d)
463
464 end subroutine initd_
465
466!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
467!    Math and Computer Science Division, Argonne National Laboratory   !
468!BOP -------------------------------------------------------------------
469!
470! !IROUTINE: initr_ - initialize MCTWorld from global root
471!
472! !DESCRIPTION:
473! Initialize MCTWorld using information valid only on the global root.
474! This is called by initm\_ but could also be called by the user
475! for very complex model--processor geometries.
476!
477! !INTERFACE:
478
479 subroutine initr_(ncomps,globalcomm,rnprocspid,ridGprocid)
480!
481! !USES:
482!
483      use m_mpif90
484      use m_die
485      use m_stdio
486
487      implicit none
488
489! !INPUT PARAMETERS:
490
491      integer, intent(in)                :: ncomps     ! total number of components
492      integer, intent(in)                :: globalcomm ! the global communicator
493      integer, dimension(:),intent(in)   :: rnprocspid ! number of processors for each component
494      integer, dimension(:,:),intent(in) :: ridGprocid ! an array of size (1:ncomps) x (0:Gsize-1)
495                                                       ! which maps local ranks to global ranks
496                                                       ! it's actually 1:Gsize here
497
498! !REVISION HISTORY:
499! 22Jun01 - R. Jacob <jacob@mcs.anl.gov> - initial prototype
500!EOP ___________________________________________________________________
501!
502  character(len=*),parameter :: myname_=myname//'::initr_'
503  integer :: ier,Gsize,myGid,MCTcomm,i,j
504
505! Check that ncomps is a legal value
506  if(ncomps < 1) then
507     call die(myname_, "argument ncomps can't less than one!",ncomps)
508  endif
509
510! determine overall size
511  call MP_comm_size(globalcomm,Gsize,ier)
512  if(ier /= 0) call MP_perr_die(myname_,'MP_comm_size()',ier)
513
514! determine my rank in comm_world
515  call MP_comm_rank(globalcomm,myGid,ier)
516  if(ier /= 0) call MP_perr_die(myname_,'MP_comm_rank()',ier)
517
518! create the MCT comm world
519  call MP_comm_dup(globalcomm,MCTcomm,ier)
520  if(ier /= 0) call MP_perr_die(myname_,'MP_comm_dup()',ier)
521
522  allocate(ThisMCTWorld%nprocspid(ncomps),stat=ier)
523  if(ier/=0) call die(myname_,'allocate(MCTWorld%nprocspid(:),...',ier)
524  allocate(ThisMCTWorld%idGprocid(ncomps,0:Gsize-1),stat=ier)
525  if(ier/=0) call die(myname_,'allocate(MCTWorld%nprocspid(:),...',ier)
526
527!  set the MCTWorld
528  ThisMCTWorld%ncomps = ncomps
529  ThisMCTWorld%MCT_comm = MCTcomm
530  ThisMCTWorld%mygrank = myGid
531
532! Now store the component ids in the World description and Broadcast
533  if(myGid == 0) then
534    ThisMCTWorld%nprocspid(1:ncomps) = rnprocspid(1:ncomps)
535    ThisMCTWorld%idGprocid = ridGprocid
536  endif
537
538  call MPI_BCAST(ThisMCTWorld%nprocspid, ncomps, MP_INTEGER, 0, MCTcomm, ier)
539  if(ier/=0) call MP_perr_die(myname_,'MPI_BCast nprocspid',ier)
540
541  call MPI_BCAST(ThisMCTWorld%idGprocid, ncomps*Gsize,MP_INTEGER, 0,MCTcomm, ier)
542  if(ier/=0) call MP_perr_die(myname_,'MPI_BCast Gprocids',ier)
543
544! if(myGid==17) then
545!      do i=1,ThisMCTWorld%ncomps
546!       do j=1,ThisMCTWorld%nprocspid(i)
547!     write(*,*)'MCTK',myGid,i,j-1,ThisMCTWorld%idGprocid(i,j-1)
548!    enddo
549!   enddo
550! endif
551
552 end subroutine initr_
553
554!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
555!    Math and Computer Science Division, Argonne National Laboratory   !
556!BOP -------------------------------------------------------------------
557!
558! !IROUTINE: clean_ - Destroy a MCTWorld
559!
560! !DESCRIPTION:
561! This routine deallocates the arrays of {\tt ThisMCTWorld}
562! It also zeros out the integer components.
563!
564! !INTERFACE:
565
566    subroutine clean_()
567!
568! !USES:
569!
570      use m_die
571
572      implicit none
573
574! !REVISION HISTORY:
575! 19Jan01 - R. Jacob <jacob@mcs.anl.gov> - initial prototype
576! 08Feb01 - R. Jacob <jacob@mcs.anl.gov> - clean the new
577!           mygrank and mylrank
578! 20Apr01 - R. Jacob <jacob@mcs.anl.gov> - remove allids from
579!           MCTWorld datatype.  Not needed because component
580!           ids are always from 1 to number-of-components.
581! 07Jun01 - R. Jacob <jacob@mcs.anl.gov> - remove myid,mynprocs
582!           and mylrank.
583!EOP ___________________________________________________________________
584
585  character(len=*),parameter :: myname_=myname//'::clean_'
586  integer :: ier
587
588  deallocate(ThisMCTWorld%nprocspid,ThisMCTWorld%idGprocid,stat=ier)
589  if(ier /= 0) call warn(myname_,'deallocate(MCTW,...)',ier)
590
591  ThisMCTWorld%ncomps = 0
592  ThisMCTWorld%mygrank = 0
593
594 end subroutine clean_
595
596!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
597!    Math and Computer Science Division, Argonne National Laboratory   !
598!BOP -------------------------------------------------------------------
599!
600! !IROUTINE: NumComponents_ - Determine number of components in World.
601!
602! !DESCRIPTION:
603! The function {\tt NumComponents\_} takes an input {\tt MCTWorld}
604! argument {\tt World}, and returns the number of component models
605! present.
606!
607! !INTERFACE:
608
609 integer function NumComponents_(World)
610!
611! !USES:
612!
613      use m_die
614      use m_stdio
615
616      implicit none
617
618! !INPUT PARAMETERS:
619
620      type(MCTWorld), intent(in)      :: World
621
622! !REVISION HISTORY:
623! 05Feb01 - J. Larson <larson@mcs.anl.gov> - initial version
624!EOP ___________________________________________________________________
625!
626  character(len=*),parameter :: myname_=myname//'::NumComponents_'
627
628  integer :: ncomps
629
630  ncomps = World%ncomps
631
632  if(ncomps <= 0) then
633     write(stderr,'(2a,1i3)') myname,":: invalid no. of components = ",ncomps
634     call die(myname_,'ncomps = ',ncomps)
635  endif
636
637  NumComponents_ = ncomps
638
639 end function NumComponents_
640
641!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
642!    Math and Computer Science Division, Argonne National Laboratory   !
643!BOP -------------------------------------------------------------------
644!
645! !IROUTINE: ComponentNumProcs_ - Number of processes a component owns.
646!
647! !DESCRIPTION:
648! The function {\tt ComponentNumProcs\_} takes an input {\tt MCTWorld}
649! argument {\tt World}, and a component ID {\tt comp\_id}, and returns
650! the number of processes owned by that component.
651!
652! !INTERFACE:
653
654 integer function ComponentNumProcs_(World, comp_id)
655!
656! !USES:
657!
658      use m_die
659      use m_stdio
660
661      implicit none
662
663! !INPUT PARAMETERS:
664      type(MCTWorld), intent(in)      :: World
665      integer,        intent(in)      :: comp_id
666
667! !REVISION HISTORY:
668! 05Feb01 - J. Larson <larson@mcs.anl.gov> - initial version
669! 07Jun01 - R. Jacob <jacob@mcs.anl.gov> - modify to use
670!           nprocspid and comp_id instead of World%mynprocs
671!EOP ___________________________________________________________________
672!
673  character(len=*),parameter :: myname_=myname//'::ComponentNumPros_'
674
675  integer :: mynprocs
676
677  mynprocs = World%nprocspid(comp_id)
678
679  if(mynprocs <= 0) then
680     write(stderr,'(2a,1i6)') myname,":: invalid no. of processes = ",mynprocs
681     call die(myname_,'Number of processes = ',mynprocs)
682  endif
683
684  ComponentNumProcs_ = mynprocs
685
686 end function ComponentNumProcs_
687
688!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
689!    Math and Computer Science Division, Argonne National Laboratory   !
690!BOP -------------------------------------------------------------------
691!
692! !IROUTINE: ComponentToWorldRank_ - Determine rank on COMM_WORLD.
693!
694! !DESCRIPTION:
695! The function {\tt ComponentToWorldRank\_} takes an input component ID
696! {\tt comp\_id} and input rank on that component communicator
697! {\tt comp\_rank}, and returns the rank of that process on the world
698! communicator of {\tt MCTWorld}. 
699!
700! !INTERFACE:
701
702 integer function ComponentToWorldRank_(comp_rank, comp_id, World)
703!
704! !USES:
705!
706      use m_die
707      use m_stdio
708
709      implicit none
710 
711! !INPUT PARAMETERS:
712      integer, intent(in)            :: comp_rank ! process rank on the communicator
713                                                  ! associated with comp_id
714      integer, intent(in)            :: comp_id   ! component id
715      type(MCTWorld), intent(in)     :: World     ! World
716
717
718! !REVISION HISTORY:
719!       05Feb01 - J. Larson <larson@mcs.anl.gov> - initial version
720!       14Jul02 - E. Ong <eong@mcs.anl.gov> - made argument checking required
721!EOP ___________________________________________________________________
722!
723  character(len=*),parameter :: myname_=myname//'::ComponentToWorldRank_'
724
725  logical :: valid
726  integer :: n, world_rank
727
728
729      ! Do we want the potentially time-consuming argument checks?
730      ! The first time we use this function during execution on a
731      ! given set of components and component ranks, we will.  In
732      ! later invocations, these argument checks are probably not
733      ! necessary (unless one alters MCTWorld), and impose a cost
734      ! one may wish to avoid.
735
736      ! These checks are just conditional statements and are
737      ! not particularly time-consuming. It's better to be safe
738      ! than sorry. -EONG
739
740
741      ! Check argument comp_id for validity--assume initially it is not...
742
743  valid = .false.
744  n = 0
745
746  if((comp_id <= World%ncomps) .and. &
747       (comp_id > 0)) then
748     valid = .true.
749  endif
750 
751  if(.not. valid) then
752     write(stderr,'(2a,1i7)') myname,":: invalid component id no. = ",&
753          comp_id
754     call die(myname_,'invalid comp_id = ',comp_id)
755  endif
756
757      ! Check argument comp_rank for validity on the communicator associated
758      ! with comp_id.  Assume initialy it is invalid.
759
760  valid = .false.
761 
762  if((0 <= comp_rank) .or. &
763       (comp_rank < ComponentNumProcs_(World, comp_id))) then
764     valid = .true.
765  endif
766
767  if(.not. valid) then
768     write(stderr,'(2a,1i5,1a,1i2)') myname, &
769          ":: invalid process ID. = ", &
770          comp_rank, "on component ",comp_id
771     call die(myname_,'invalid comp_rank = ',comp_rank)
772  endif
773
774
775      ! If we have reached this point, the input data are valid.
776      ! Return the global rank for comp_rank on component comp_id
777
778  world_rank = World%idGprocid(comp_id, comp_rank)
779
780  if(world_rank < 0) then
781     write(stderr,'(2a,1i6)') myname,":: negative world rank = ",world_rank
782     call die(myname_,'negative world rank = ',world_rank)
783  endif   
784
785  ComponentToWorldRank_ = world_rank
786
787 end function ComponentToWorldRank_
788
789!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
790!    Math and Computer Science Division, Argonne National Laboratory   !
791!BOP -------------------------------------------------------------------
792!
793! !IROUTINE: ComponentRootRank_ - Rank of component root on COMM_WORLD.
794!
795! !DESCRIPTION:
796! The function {\tt ComponentRootRank\_} takes an input component ID
797! {\tt comp\_id} and input {\tt MCTWorld} variable {\tt World}, and
798! returns the global rank of the root of this component. 
799!
800! !INTERFACE:
801
802 integer function ComponentRootRank_(comp_id, World)
803!
804! !USES:
805!
806      use m_die
807      use m_stdio
808
809      implicit none
810
811! !INPUT PARAMETERS:
812      integer, intent(in)            :: comp_id   ! component id
813      type(MCTWorld), intent(in)     :: World     ! World
814
815! !REVISION HISTORY:
816!       05Feb01 - J. Larson <larson@mcs.anl.gov> - initial version
817!       14Jul02 - E. Ong <eong@mcs.anl.gov> - made argument checking required
818!EOP ___________________________________________________________________
819!
820  character(len=*),parameter :: myname_=myname//'::ComponentRootRank_'
821
822  integer :: world_comp_root
823
824      ! Call ComponentToWorldRank_ assuming the root on a remote component
825      ! has rank zero on the communicator associated with that component.
826
827  world_comp_root = ComponentToWorldRank_(0, comp_id, World)
828
829  if(world_comp_root < 0) then
830     write(stderr,'(2a,1i6)') myname,":: negative world rank = ",& 
831          world_comp_root
832     call die(myname_,'invalid root id = ',world_comp_root)
833  endif   
834
835  ComponentRootRank_ = world_comp_root
836
837 end function ComponentRootRank_
838
839 end module m_MCTWorld
840
Note: See TracBrowser for help on using the repository browser.