source: CPL/oasis3-mct/branches/OASIS3-MCT_5.0_branch/lib/psmile/src/mod_oasis_method.F90 @ 6331

Last change on this file since 6331 was 6331, checked in by aclsce, 17 months ago

Moved oasis-mct_5.0 in oasis3-mct/branches directory.

File size: 31.9 KB
Line 
1
2!> High level OASIS user interfaces
3
4MODULE mod_oasis_method
5
6   USE mod_oasis_kinds
7   USE mod_oasis_mem
8   USE mod_oasis_sys
9   USE mod_oasis_data
10   USE mod_oasis_parameters
11   USE mod_oasis_namcouple
12   USE mod_oasis_part
13   USE mod_oasis_var
14   USE mod_oasis_coupler
15   USE mod_oasis_advance
16   USE mod_oasis_timer
17   USE mod_oasis_ioshr
18   USE mod_oasis_grid
19   USE mod_oasis_mpi
20   USE mod_oasis_string
21   USE mod_oasis_load_balancing
22   USE mct_mod
23
24   IMPLICIT NONE
25
26   private
27
28   public oasis_init_comp
29   public oasis_terminate
30   public oasis_enddef
31
32#ifdef __VERBOSE
33   integer(kind=ip_intwp_p),parameter :: debug=2
34#else
35   integer(kind=ip_intwp_p),parameter :: debug=1
36#endif
37   logical :: lg_mpiflag
38
39CONTAINS
40
41!----------------------------------------------------------------------
42
43!> OASIS user init method
44
45   SUBROUTINE oasis_init_comp(mynummod,cdnam,kinfo,coupled,commworld)
46
47   !> * This is COLLECTIVE, all pes must call
48
49   IMPLICIT NONE
50
51   INTEGER (kind=ip_intwp_p),intent(out)   :: mynummod     !< component model ID
52   CHARACTER(len=*)         ,intent(in)    :: cdnam        !< model name
53   INTEGER (kind=ip_intwp_p),intent(inout),optional :: kinfo  !< return code
54   logical                  ,intent(in)   ,optional :: coupled  !< flag to specify whether this component is coupled in oasis
55   integer (kind=ip_intwp_p),intent(in)   ,optional :: commworld  !< user defined mpi_comm_world to use in oasis
56!  ---------------------------------------------------------
57   integer(kind=ip_intwp_p) :: ierr
58   INTEGER(kind=ip_intwp_p) :: n,nns,iu
59   integer(kind=ip_intwp_p) :: icolor,ikey
60   CHARACTER(len=ic_med)    :: filename,filename2
61   character(len=ic_med)    :: pio_type
62   integer(kind=ip_intwp_p) :: pio_stride
63   integer(kind=ip_intwp_p) :: pio_root
64   integer(kind=ip_intwp_p) :: pio_numtasks
65   INTEGER(kind=ip_intwp_p),ALLOCATABLE :: tmparr(:)
66   INTEGER(kind=ip_intwp_p) :: k,i,m,k1,k2
67   INTEGER(kind=ip_intwp_p) :: nt
68   INTEGER(kind=ip_intwp_p) :: nvar
69   INTEGER(kind=ip_intwp_p) :: mall
70   logical                  :: found
71   logical,pointer          :: coupledlist(:)
72   character(len=ic_lvar)   :: tmp_modnam
73   logical                  :: tmp_modcpl
74   character(len=ic_lvar)   :: i_name
75   character(len=*),parameter :: subname = '(oasis_init_comp)'
76
77   character(len=MPI_MAX_PROCESSOR_NAME), dimension(:), allocatable :: cla_nodes
78   character(len=MPI_MAX_PROCESSOR_NAME) :: cl_node
79   integer :: il_nodelen
80   integer, dimension(:), allocatable :: ila_colors
81!  ---------------------------------------------------------
82
83   if (present(kinfo)) then
84      kinfo = OASIS_OK
85   endif
86
87
88   call oasis_data_zero()
89
90   oasis_coupled = .true.
91   if (present(coupled)) then
92      oasis_coupled = coupled
93   endif
94
95   mpi_comm_global_world = MPI_COMM_WORLD
96   if (present(commworld)) then
97     mpi_comm_global_world = commworld
98   endif
99
100   !------------------------
101   !> * Initialize MPI
102   !------------------------
103
104   lg_mpiflag = .FALSE.
105   CALL MPI_Initialized ( lg_mpiflag, ierr )
106   IF ( .NOT. lg_mpiflag ) THEN
107      if (OASIS_debug >= 10) WRITE (0,FMT='(A)') subname//': Calling MPI_Init'
108      CALL MPI_INIT ( ierr )
109   else
110      if (OASIS_debug >= 10) WRITE (0,FMT='(A)') subname//': Not Calling MPI_Init'
111   ENDIF
112
113!  Intitialise load imbalance counters
114   call oasis_lb_init
115
116! Initial default for early part of init
117#ifdef use_comm_MPI1
118   mpi_comm_global = mpi_comm_global_world
119#elif defined use_comm_MPI2
120   mpi_comm_global = ??
121#endif
122
123   CALL MPI_Comm_Size(mpi_comm_global_world,mpi_size_world,ierr)
124   CALL MPI_Comm_Rank(mpi_comm_global_world,mpi_rank_world,ierr)
125   mpi_rank_global = mpi_rank_world
126
127   !------------------------
128   !> * Set initial output file, need mpi_rank_world
129   !------------------------
130
131   iu=-1
132
133   call oasis_unitsetmin(1024)
134   call oasis_unitsetmax(9999)
135   IF (mpi_rank_world == 0) THEN
136       CALL oasis_unitget(iu)
137       nulprt1 = iu
138       WRITE(filename,'(a,i6.6)') 'nout.',mpi_rank_world
139       OPEN(nulprt1,file=filename)
140   ENDIF
141
142   !------------------------
143   !> * Initialize namcouple.
144   !>   First on rank 0 to write error messages
145   !>   then on all other ranks.  All tasks will
146   !>   read the namcouple file independently.
147   !------------------------
148
149   IF (mpi_rank_world == 0) THEN
150      call oasis_namcouple_init()
151   endif
152   call oasis_mpi_barrier(mpi_comm_global_world)
153   IF (mpi_rank_world /= 0) THEN
154      call oasis_namcouple_init()
155   endif
156   OASIS_debug = namlogprt
157   TIMER_debug = namtlogprt
158   cdf_filetype = trim(namcdftyp)
159   call oasis_unitsetmin(namuntmin)
160   call oasis_unitsetmax(namuntmax)
161   allow_no_restart = namnorest
162
163   ! If namelist load balancing variable > 0, activate event timeline analysis
164   IF ( namlblogprt > 0 ) ET_debug = .TRUE.
165
166   !------------------------
167   !> * Check if NFIELDS=0, there is no coupling.
168   ! No information must be written in the debug files as
169   ! the different structures are not allocated
170   !------------------------
171
172   IF ( nnamcpl == 0 ) THEN
173       IF (mpi_rank_world == 0) THEN
174           WRITE (UNIT = nulprt1,FMT = *) subname,wstr, &
175              'The models are not exchanging any field ($NFIELDS = 0) '
176           WRITE (UNIT = nulprt1,FMT = *)  &
177              'so we force OASIS_debug = 0 for all processors '
178           CALL oasis_flush(nulprt1)
179       ENDIF
180       OASIS_debug = 0
181   ENDIF
182
183   !------------------------
184   !> * Determine the total number of coupling fields from namcouple.
185   !>   Set maxvar parameter and allocate prism_var.
186   ! to avoid a parameter in oasis_def_var and mod_oasis_coupler
187   !------------------------
188
189   size_namfld=0
190   DO n = 1,nnamcpl
191     size_namfld = size_namfld + oasis_string_listGetNum(namsrcfld(n))
192   ENDDO
193   maxvar = size_namfld * 2    ! multiply by 2 to allow sending to self
194   IF (mpi_rank_world == 0) THEN
195       WRITE (UNIT = nulprt1,FMT = *) 'Total number of coupling fields :',maxvar
196       CALL oasis_flush(nulprt1)
197   ENDIF
198
199   ALLOCATE(prism_var(maxvar))
200
201   !------------------------
202   !> * Store all the names of the fields exchanged in the namcouple
203   ! which can be different of namsrcfld(:) and namdstfld(:) if multiple
204   ! fields are exchanged together
205   !------------------------
206
207   ALLOCATE(total_namsrcfld(size_namfld))
208   ALLOCATE(total_namdstfld(size_namfld))
209   total_namsrcfld = ''
210   total_namdstfld = ''
211
212   m=0
213   DO nns = 1,nnamcpl
214     n = namsort2nn(nns)
215     k1=oasis_string_listGetNum(namsrcfld(n))
216     k2=oasis_string_listGetNum(namdstfld(n))
217     if (k1 /= k2) then
218       WRITE(nulprt1,*) subname,estr,'namcouple fields do not agree in number'
219       WRITE(nulprt1,*) subname,estr,'namsrcfld = ',trim(namsrcfld(n))
220       WRITE(nulprt1,*) subname,estr,'namdstfld = ',trim(namdstfld(n))
221       WRITE(nulprt1,*) subname,estr,'check your namcouple file '
222       call oasis_abort(file=__FILE__,line=__LINE__)
223     endif
224     DO i=1,k1
225       m=m+1
226       CALL oasis_string_listGetName(namsrcfld(n),i,i_name)
227       total_namsrcfld(m)=trim(i_name)
228       CALL oasis_string_listGetName(namdstfld(n),i,i_name)
229       total_namdstfld(m)=trim(i_name)
230     ENDDO
231   ENDDO
232   nvar = m
233
234   IF (OASIS_Debug >= 15 .and. mpi_rank_world == 0) THEN
235      DO m=1,nvar
236         WRITE (UNIT = nulprt1,FMT = *) subname,'Coupling fields  namsrcfld:',&
237                                     TRIM(total_namsrcfld(m))
238         WRITE (UNIT = nulprt1,FMT = *) subname,'Coupling fields namdstfld:',&
239                                     TRIM(total_namdstfld(m))
240         CALL oasis_flush(nulprt1)
241      ENDDO
242   ENDIF
243
244   !------------------------
245   ! check (not needed anymore)
246   !------------------------
247
248   if (len_trim(cdnam) > ic_lvar) then
249      WRITE(nulprt1,*) subname,estr,'model name too long = ',trim(cdnam)
250      write(nulprt1,*) subname,estr,'max model name length = ',ic_lvar
251      call oasis_abort(file=__FILE__,line=__LINE__)
252   endif
253
254   !------------------------
255   !> * Gather model names from all tasks to generate active model list on all tasks.
256   !--- Check that the coupled flag from all tasks is consistent for a given model or abort
257   !--- Size of compnm is ic_lvar
258   !------------------------
259
260   compnm = trim(cdnam)
261   allocate(compnmlist(mpi_size_world))
262   allocate(coupledlist(mpi_size_world))
263   call MPI_GATHER(compnm, ic_lvar, MPI_CHARACTER, compnmlist, ic_lvar, MPI_CHARACTER, 0, mpi_comm_global_world, ierr)
264   call MPI_GATHER(oasis_coupled, 1, MPI_LOGICAL, coupledlist, 1, MPI_LOGICAL, 0, mpi_comm_global_world, ierr)
265
266   prism_nmodels = 0
267   prism_modnam(:) = ' '
268   prism_modcpl(:) = .false.
269   if (mpi_rank_world == 0) then
270      if (OASIS_Debug >= 15) then
271         do n = 1,mpi_size_world
272            write(nulprt1,*) subname,' compnm gather ',n,trim(compnmlist(n)),coupledlist(n)
273            call oasis_flush(nulprt1)
274         enddo
275      endif
276
277      !--- generate unique list of models and coupling status
278      !--- check for coupled flag consistency
279      do n = 1,mpi_size_world
280         found = .false.
281         m = 0
282         do while (.not.found .and. m < prism_nmodels)
283            m = m + 1
284            if (compnmlist(n) == prism_modnam(m)) then
285               found = .true.
286               if (coupledlist(n) .neqv. prism_modcpl(m)) then
287                  WRITE(nulprt1,*) subname,estr,'inconsistent coupled flag'
288                  WRITE(nulprt1,*) subname,estr,'the optional argument, coupled'
289                  WRITE(nulprt1,*) subname,estr,'must be identical on all tasks of a component.'
290                  call oasis_abort(file=__FILE__,line=__LINE__)
291               endif
292            endif
293         enddo
294         if (.not.found) then
295            prism_nmodels = prism_nmodels + 1
296            if (prism_nmodels > prism_mmodels) then
297               WRITE(nulprt1,*) subname,estr,'prism_nmodels too large, increase prism_mmodels in mod_oasis_data'
298               call oasis_abort(file=__FILE__,line=__LINE__)
299            endif
300            prism_modnam(prism_nmodels) = trim(compnmlist(n))
301            prism_modcpl(prism_nmodels) = coupledlist(n)
302         endif
303      enddo
304
305      !--- sort so coupled are first, uncoupled are last
306      !--- makes using only active models via "prism_amodels" easier
307      prism_amodels = prism_nmodels
308      do n = prism_nmodels,1,-1
309         if (.not.prism_modcpl(n)) then
310            tmp_modnam = prism_modnam(n)
311            tmp_modcpl = prism_modcpl(n)
312            do m = n,prism_nmodels-1
313               prism_modnam(m) = prism_modnam(m+1)
314               prism_modcpl(m) = prism_modcpl(m+1)
315            enddo
316            prism_modnam(prism_nmodels) = tmp_modnam
317            prism_modcpl(prism_nmodels) = tmp_modcpl
318            prism_amodels = prism_amodels - 1
319         endif
320      enddo
321
322      !--- document and check list
323      do n = 1,prism_amodels
324         write(nulprt1,*) subname,'   COUPLED models ',n,trim(prism_modnam(n)),prism_modcpl(n)
325         if (.not.prism_modcpl(n)) then
326            WRITE(nulprt1,*) subname,estr,'model expected to be coupled but is not = ',trim(prism_modnam(n))
327            call oasis_abort(file=__FILE__,line=__LINE__)
328         endif
329         call oasis_flush(nulprt1)
330      enddo
331      do n = prism_amodels+1,prism_nmodels
332         write(nulprt1,*) subname,' UNCOUPLED models ',n,trim(prism_modnam(n)),prism_modcpl(n)
333         if (prism_modcpl(n)) then
334            WRITE(nulprt1,*) subname,estr,'model expected to be uncoupled but is not = ',trim(prism_modnam(n))
335            call oasis_abort(file=__FILE__,line=__LINE__)
336         endif
337         call oasis_flush(nulprt1)
338      enddo
339   endif
340
341   deallocate(coupledlist)
342
343   !------------------------
344   !> * Broadcast the model list to all MPI tasks
345   !------------------------
346   call oasis_mpi_bcast(prism_nmodels,mpi_comm_global_world,subname//' prism_nmodels')
347   call oasis_mpi_bcast(prism_amodels,mpi_comm_global_world,subname//' prism_amodels')
348   call oasis_mpi_bcast(prism_modnam ,mpi_comm_global_world,subname//' prism_modnam')
349   call oasis_mpi_bcast(prism_modcpl ,mpi_comm_global_world,subname//' prism_modcpl')
350
351   !------------------------
352   !> * Compute compid
353   !------------------------
354
355   compid = -1
356   do n = 1,prism_nmodels
357      if (trim(cdnam) == trim(prism_modnam(n))) compid = n
358   enddo
359   mynummod = compid
360   IF (mpi_rank_world == 0) THEN
361      WRITE(nulprt1,*) subname, 'cdnam :',TRIM(cdnam),' mynummod :',mynummod
362      CALL oasis_flush(nulprt1)
363   ENDIF
364
365! tcraig, this should never happen based on logic above
366   if (compid < 0) then
367      WRITE(nulprt1,*) subname,estr,'prism_modnam internal inconsistency = ',TRIM(cdnam)
368      call oasis_abort(file=__FILE__,line=__LINE__)
369   endif
370
371   !------------------------
372   !> * Re-Set MPI info based on active model tasks
373   !  (need compid for MPI1 COMM_SPLIT)
374   !------------------------
375
376   mpi_rank_global = -1
377#ifdef use_comm_MPI1
378
379   !------------------------
380   !>   * Set mpi_comm_local based on compid
381   !------------------------
382
383   ikey = 0
384   icolor = compid
385   call MPI_COMM_SPLIT(mpi_comm_global_world,icolor,ikey,mpi_comm_local,ierr)
386
387   !------------------------
388   !>   * Set mpi_comm_global based on oasis_coupled flag
389   !------------------------
390
391   ikey = 0
392   icolor = 1
393   if (.not.oasis_coupled) icolor = 0
394   call MPI_COMM_SPLIT(mpi_comm_global_world,icolor,ikey,mpi_comm_global,ierr)
395!tcx   if (.not.oasis_coupled) mpi_comm_global = MPI_COMM_NULL
396
397#elif defined use_comm_MPI2
398
399   mpi_comm_global = ??
400   mpi_comm_local = mpi_comm_global_world
401
402#endif
403
404   !------------------------
405   !> * Reset debug levels
406   !  verbose level disabled if load balance analysis
407   !------------------------
408
409   IF ( ET_debug .AND. OASIS_debug > 0 ) THEN
410      WRITE (UNIT = nulprt1,FMT = *) subname,wstr, &
411       ' WARNING: With load balance analysis '
412      WRITE (UNIT = nulprt1,FMT = *)  &
413       ' OASIS_debug should be 0 '
414      CALL oasis_flush(nulprt1)
415   ENDIF
416
417   IF (mpi_rank_world == 0) CLOSE(nulprt1)
418
419   if (.not.oasis_coupled) then
420      return
421   endif
422
423   CALL MPI_Comm_Size(mpi_comm_global,mpi_size_global,ierr)
424   CALL MPI_Comm_Rank(mpi_comm_global,mpi_rank_global,ierr)
425
426   CALL MPI_Comm_Size(mpi_comm_local,mpi_size_local,ierr)
427   CALL MPI_Comm_Rank(mpi_comm_local,mpi_rank_local,ierr)
428   mpi_root_local = 0
429
430#ifdef use_comm_MPI1
431
432   !------------------------
433   !>   * Set mpi_comm_map based on node association
434   !------------------------
435
436   CALL MPI_Get_processor_name(mpi_node_name, il_nodelen, ierr)
437
438   IF (mpi_rank_local == mpi_root_local) THEN
439
440      ! Prepare working memory on local root
441
442      ALLOCATE(cla_nodes(mpi_size_local))
443      ALLOCATE(ila_colors(mpi_size_local))
444      cla_nodes(:) = ''
445      ila_colors(:) = -1
446   ELSE
447      ALLOCATE(cla_nodes(1))
448      ALLOCATE(ila_colors(1))
449   END IF
450
451   CALL MPI_Gather (mpi_node_name,MPI_MAX_PROCESSOR_NAME,MPI_CHAR,&
452      &             cla_nodes,    MPI_MAX_PROCESSOR_NAME,MPI_CHAR,&
453      &             mpi_root_local, mpi_comm_local, ierr)
454
455   IF (mpi_rank_local == mpi_root_local) THEN
456
457      ! Pick only on proc per node
458
459      DO WHILE (ANY(ila_colors == -1))
460         cl_node = cla_nodes(MINLOC(ila_colors,DIM=1))
461         ila_colors(MINLOC(ila_colors,DIM=1)) = 1
462         DO i = MINLOC(ila_colors,DIM=1), mpi_size_local
463            IF (ila_colors(i) == -1 .AND. cla_nodes(i) == cl_node)&
464               & ila_colors(i) = 0
465         END DO
466      END DO
467   END IF
468
469   icolor = 0
470   CALL MPI_Scatter (ila_colors,1,MPI_INT,&
471      &              icolor,    1,MPI_INT,&
472      &              mpi_root_local, mpi_comm_local, ierr)
473
474   mpi_in_map = icolor == 1
475
476   ikey = 1
477   CALL MPI_Comm_split(mpi_comm_local,icolor,ikey,mpi_comm_map,ierr)
478
479   IF (mpi_in_map) THEN
480      CALL MPI_Comm_size(mpi_comm_map,mpi_size_map,ierr)
481      CALL MPI_Comm_rank(mpi_comm_map,mpi_rank_map,ierr)
482   END IF
483
484   IF (mpi_rank_local == mpi_root_local) THEN
485
486      ! Set the root of the mapping subcommunicator on the
487      ! local communicator root process
488
489      mpi_root_map = mpi_rank_map
490
491   END IF
492
493   ! Free work memory on local root
494
495   DEALLOCATE(cla_nodes)
496   DEALLOCATE(ila_colors)
497
498
499#elif defined use_comm_MPI2
500
501   mpi_comm_map = ??
502   mpi_in_map   = ??
503
504#endif
505   !------------------------
506   !> * Open log files
507   !------------------------
508
509   iu=-1
510   CALL oasis_unitget(iu)
511   nulprt=iu
512   IF (OASIS_debug <= 1) THEN
513       WRITE(filename ,'(a,i2.2)') 'debug.root.',compid
514       WRITE(filename2,'(a,i2.2)') 'debug.notroot.',compid
515       IF (mpi_rank_local == 0) THEN
516           OPEN(nulprt,file=filename,status='REPLACE')
517           WRITE(nulprt,'(2a,2i8)') subname,' OASIS RUNNING '
518           WRITE(nulprt,'(2a,2i8)') subname,' OPEN debug file for pe, unit :',mpi_rank_local,nulprt
519           call oasis_flush(nulprt)
520       ENDIF
521       IF (mpi_rank_local == 1) THEN
522           OPEN(nulprt,file=filename2,status='REPLACE')
523           WRITE(nulprt,'(2a,2i8)') subname,' OASIS RUNNING '
524           WRITE(nulprt,'(2a,2i8)') subname,' OPEN debug file for pe, unit :',mpi_rank_local,nulprt
525           CALL oasis_flush(nulprt)
526       ENDIF
527
528       call oasis_mpi_barrier(mpi_comm_local)
529
530       IF (mpi_rank_local > 1) THEN
531           OPEN(nulprt,file=filename2,position='APPEND')
532           !WRITE(nulprt,'(2a,2i8)') subname,' OASIS RUNNING '
533           !WRITE(nulprt,'(2a,2i8)') subname,' OPEN debug file for pe, unit :',mpi_rank_local,nulprt
534           !CALL oasis_flush(nulprt)
535       ENDIF
536   ELSE
537       WRITE(filename,'(a,i2.2,a,i6.6)') 'debug.',compid,'.',mpi_rank_local
538       OPEN(nulprt,file=filename,status='REPLACE')
539       WRITE(nulprt,'(2a,2i8)') subname,' OPEN debug file, for pe, unit :',mpi_rank_local,nulprt
540       CALL oasis_flush(nulprt)
541   ENDIF
542
543   IF ( (OASIS_debug == 1) .AND. (mpi_rank_local == 0)) OASIS_debug=10
544
545   IF (OASIS_debug >= 2) THEN
546       WRITE(nulprt,'(3a,i8)') subname,' model compid ',TRIM(cdnam),compid
547       CALL oasis_flush(nulprt)
548   ENDIF
549
550   iu=-1
551   CALL oasis_unitget(iu)
552
553   IF ( ET_debug .AND. mpi_size_global == 0 ) nulet=iu
554
555   call oasis_debug_enter(subname)
556
557   !------------------------
558   !> * Set mpi_root_global
559   ! (after nulprt set)
560   !------------------------
561
562   call mod_oasis_setrootglobal()
563
564   !------------------------
565   !--- PIO
566   !------------------------
567#if (PIO_DEFINED)
568! tcraig, not working as of Oct 2011
569   pio_type = 'netcdf'
570   pio_stride = -99
571   pio_root = -99
572   pio_numtasks = -99
573   call oasis_ioshr_init(mpi_comm_local,pio_type,pio_stride,pio_root,pio_numtasks)
574#endif
575
576   !------------------------
577   !> * Memory Initialization
578   !------------------------
579
580   IF (OASIS_debug >= 2)  THEN
581       CALL oasis_mem_init(nulprt)
582       CALL oasis_mem_print(nulprt,subname)
583   ENDIF
584
585   !------------------------
586   !> * Timer Initialization
587   !------------------------
588
589   ! Allocate timer memory based on maxvar
590   nt = 7*maxvar+100
591   call oasis_timer_init (trim(cdnam), trim(cdnam)//'.timers',nt)
592   call oasis_timer_start('total')
593   call oasis_timer_start('init_thru_enddef')
594
595   !------------------------
596   !> * Diagnostics
597   !------------------------
598
599   if (OASIS_debug >= 15)  then
600      write(nulprt,*) subname,' compid         = ',compid
601      write(nulprt,*) subname,' compnm         = ',trim(compnm)
602      write(nulprt,*) subname,' node name      = ',trim(mpi_node_name)
603      write(nulprt,*) subname,' mpi_comm_world = ',mpi_comm_global_world
604      write(nulprt,*) subname,' mpi_comm_global= ',mpi_comm_global
605      write(nulprt,*) subname,'     size_global= ',mpi_size_global
606      write(nulprt,*) subname,'     rank_global= ',mpi_rank_global
607      write(nulprt,*) subname,' mpi_comm_local = ',mpi_comm_local
608      write(nulprt,*) subname,'     size_local = ',mpi_size_local
609      write(nulprt,*) subname,'     rank_local = ',mpi_rank_local
610      write(nulprt,*) subname,'     root_local = ',mpi_root_local
611      write(nulprt,*) subname,' mpi_in_map     = ',mpi_in_map
612      write(nulprt,*) subname,' mpi_comm_map   = ',mpi_comm_map
613      write(nulprt,*) subname,'     size_map   = ',mpi_size_map
614      write(nulprt,*) subname,'     rank_map   = ',mpi_rank_map
615      write(nulprt,*) subname,'     root_map   = ',mpi_root_map
616      write(nulprt,*) subname,' OASIS_debug    = ',OASIS_debug
617      write(nulprt,*) subname,' cdf_filetype   = ',trim(cdf_filetype)
618      do n = 1,prism_amodels
619         write(nulprt,*) subname,'   n,prism_model,root = ',&
620            n,TRIM(prism_modnam(n)),mpi_root_global(n)
621      enddo
622      call oasis_flush(nulprt)
623   endif
624
625   call oasis_debug_exit(subname)
626
627 END SUBROUTINE oasis_init_comp
628
629!----------------------------------------------------------------------
630
631!> OASIS user finalize method
632
633   SUBROUTINE oasis_terminate(kinfo)
634
635   IMPLICIT NONE
636
637   INTEGER (kind=ip_intwp_p),intent(inout),optional :: kinfo  !< return code
638!  ---------------------------------------------------------
639   integer(kind=ip_intwp_p) :: ierr
640   character(len=*),parameter :: subname = '(oasis_terminate)'
641!  ---------------------------------------------------------
642
643   call oasis_debug_enter(subname)
644
645
646   if (.not. oasis_coupled) then
647      deallocate(compnmlist)
648      call oasis_debug_exit(subname)
649      return
650   endif
651
652   if (present(kinfo)) then
653      kinfo = OASIS_OK
654   endif
655
656   !------------------------
657   !> * Print timer information
658   !------------------------
659
660   call oasis_timer_stop('total')
661   call oasis_timer_print()
662
663   !------------------------------------
664   !> * Print load balancing information
665   !------------------------------------
666   IF (ET_debug) call oasis_lb_print(trim(compnm),namruntim)
667
668   deallocate(compnmlist)
669
670   !------------------------
671   !> * Call MPI finalize
672   !------------------------
673
674   IF ( .NOT. lg_mpiflag ) THEN
675       IF (OASIS_debug >= 2)  THEN
676           WRITE (nulprt,FMT='(A)') subname//': Calling MPI_Finalize'
677           CALL oasis_flush(nulprt)
678       ENDIF
679       CALL MPI_Finalize ( ierr )
680   else
681       IF (OASIS_debug >= 2)  THEN
682           WRITE (nulprt,FMT='(A)') subname//': Not Calling MPI_Finalize'
683           CALL oasis_flush(nulprt)
684       ENDIF
685   ENDIF
686
687   !------------------------
688   !> * Write SUCCESSFUL RUN
689   !------------------------
690   IF (OASIS_debug >= 2)  THEN
691       CALL oasis_mem_print(nulprt,subname)
692   ENDIF
693
694   IF (mpi_rank_local == 0)  THEN
695       WRITE(nulprt,*) subname,' SUCCESSFUL RUN'
696       CALL oasis_flush(nulprt)
697   ENDIF
698
699   call oasis_debug_exit(subname)
700
701   CALL oasis_flush(nulprt)
702   close(nulprt)
703
704 END SUBROUTINE oasis_terminate
705
706!----------------------------------------------------------------------
707
708!> OASIS user interface specifying the OASIS definition phase is complete
709
710   SUBROUTINE oasis_enddef(kinfo)
711
712   IMPLICIT NONE
713
714   INTEGER (kind=ip_intwp_p),intent(inout),optional :: kinfo  !< return code
715!  ---------------------------------------------------------
716   integer (kind=ip_intwp_p) :: n
717   integer (kind=ip_intwp_p) :: lkinfo
718   integer (kind=ip_intwp_p) :: icpl, ierr
719   integer (kind=ip_intwp_p) :: newcomm
720   logical, parameter :: local_timers_on = .false.
721   character(len=*),parameter :: subname = '(oasis_enddef)'
722!  ---------------------------------------------------------
723
724   call oasis_debug_enter(subname)
725
726   if (.not. oasis_coupled) then
727      call oasis_debug_exit(subname)
728      return
729   endif
730
731   lkinfo = OASIS_OK
732
733   if (local_timers_on .and. mpi_comm_local /= MPI_COMM_NULL) then
734      call oasis_timer_start('oasis_enddef_barrier')
735      call oasis_mpi_barrier(mpi_comm_local, subname)
736      call oasis_timer_stop('oasis_enddef_barrier')
737   endif
738
739   CALL oasis_timer_start ('oasis_enddef')
740   if (ET_debug) CALL oasis_lb_measure(-1,LB_ENDF)
741   if (local_timers_on) call oasis_timer_start('oasis_enddef_prep')
742
743   !------------------------
744   !> * Check enddef called only once per task
745   !------------------------
746
747   if (enddef_called) then
748       write(nulprt,*) subname,estr,'enddef called already'
749       call oasis_abort(file=__FILE__,line=__LINE__)
750   endif
751   enddef_called = .true.
752
753   IF (OASIS_debug >= 2)  THEN
754       CALL oasis_mem_print(nulprt,subname//':start')
755   ENDIF
756
757   !------------------------
758   !> * Reset mpi_comm_global because active tasks might have been excluded
759   !--- for changes to mpi_comm_local since init
760   !------------------------
761
762   icpl = MPI_UNDEFINED
763   if (mpi_comm_local /= MPI_COMM_NULL) icpl = 1
764   CALL MPI_COMM_Split(mpi_comm_global,icpl,1,newcomm,ierr)
765   mpi_comm_global = newcomm
766
767   !------------------------
768   !> * For active tasks only
769   !------------------------
770
771   if (local_timers_on) call oasis_timer_stop('oasis_enddef_prep')
772
773   if (mpi_comm_global /= MPI_COMM_NULL) then
774
775      if (local_timers_on) call oasis_timer_start('oasis_enddef_prep2')
776
777      !------------------------
778      !>   * Update mpi_comm_global
779      !------------------------
780
781      CALL MPI_Comm_Size(mpi_comm_global,mpi_size_global,ierr)
782      CALL MPI_Comm_Rank(mpi_comm_global,mpi_rank_global,ierr)
783
784      !------------------------
785      !>   * Update mpi_root_global
786      !------------------------
787
788      call mod_oasis_setrootglobal()
789
790      !------------------------
791      !>   * Document
792      !------------------------
793
794      if (OASIS_debug >= 2)  then
795         write(nulprt,*) subname,' compid         = ',compid
796         write(nulprt,*) subname,' compnm         = ',trim(compnm)
797         write(nulprt,*) subname,' mpi_comm_world = ',mpi_comm_global_world
798         write(nulprt,*) subname,' mpi_comm_global= ',mpi_comm_global
799         write(nulprt,*) subname,'     size_global= ',mpi_size_global
800         write(nulprt,*) subname,'     rank_global= ',mpi_rank_global
801         write(nulprt,*) subname,' mpi_comm_local = ',mpi_comm_local
802         write(nulprt,*) subname,'     size_local = ',mpi_size_local
803         write(nulprt,*) subname,'     rank_local = ',mpi_rank_local
804         write(nulprt,*) subname,'     root_local = ',mpi_root_local
805         write(nulprt,*) subname,' OASIS_debug    = ',OASIS_debug
806         do n = 1,prism_amodels
807            write(nulprt,*) subname,'   n,prism_model,root = ',&
808               n,TRIM(prism_modnam(n)),mpi_root_global(n)
809         enddo
810         CALL oasis_flush(nulprt)
811      endif
812
813      if (local_timers_on) call oasis_timer_stop('oasis_enddef_prep2')
814
815      !------------------------
816      !>   * Reconcile partitions, call part_setup
817      !--- generate gsmaps from partitions
818      !------------------------
819
820      if (local_timers_on) call oasis_timer_start('oasis_enddef_part_setup')
821      call oasis_part_setup()
822      IF (OASIS_debug >= 2)  THEN
823          CALL oasis_mem_print(nulprt,subname//':part_setup')
824      ENDIF
825      if (local_timers_on) call oasis_timer_stop('oasis_enddef_part_setup')
826
827      !------------------------
828      !>   * Reconcile variables, call var_setup
829      !------------------------
830
831      if (local_timers_on) call oasis_timer_start('oasis_enddef_var_setup')
832      call oasis_var_setup()
833      IF (OASIS_debug >= 2)  THEN
834          CALL oasis_mem_print(nulprt,subname//':var_setup')
835      ENDIF
836      if (local_timers_on) call oasis_timer_stop('oasis_enddef_var_setup')
837
838      !------------------------
839      !>   * Write grid info to files one model at a time
840      !------------------------
841
842      if (local_timers_on) call oasis_timer_start('oasis_enddef_write2files')
843      call oasis_mpi_barrier(mpi_comm_global)
844      do n = 1,prism_amodels
845         if (compid == n) then
846            call oasis_write2files()
847         endif
848         call oasis_mpi_barrier(mpi_comm_global)
849      enddo
850      IF (OASIS_debug >= 2)  THEN
851          CALL oasis_mem_print(nulprt,subname//':write2files')
852      ENDIF
853      if (local_timers_on) call oasis_timer_stop('oasis_enddef_write2files')
854
855      !------------------------
856      !>   * MCT Initialization
857      !------------------------
858
859      if (local_timers_on) call oasis_timer_start('oasis_enddef_mctworldinit')
860      call mct_world_init(prism_amodels,mpi_comm_global,mpi_comm_local,compid)
861      IF (OASIS_debug >= 2)  THEN
862         WRITE(nulprt,*) subname, ' done mct_world_init '
863         CALL oasis_flush(nulprt)
864      ENDIF
865      if (local_timers_on) call oasis_timer_stop('oasis_enddef_mctworldinit')
866
867      !------------------------
868      !>   * Initialize coupling via call to coupler_setup
869      !------------------------
870
871      if (local_timers_on) call oasis_timer_start('oasis_enddef_coupler_setup')
872      call oasis_coupler_setup()
873      IF (OASIS_debug >= 2)  THEN
874         WRITE(nulprt,*) subname, ' done prism_coupler_setup '
875         CALL oasis_flush(nulprt)
876      ENDIF
877      IF (OASIS_debug >= 2)  THEN
878          CALL oasis_mem_print(nulprt,subname//':coupler_setup')
879      ENDIF
880      if (local_timers_on) call oasis_timer_stop('oasis_enddef_coupler_setup')
881
882      !------------------------
883      !>   * Initialize partition grid data call to part_readgrid
884      !------------------------
885
886      if (local_timers_on) call oasis_timer_start('oasis_enddef_part_readgrid')
887      call oasis_part_readgrid()
888      IF (OASIS_debug >= 2)  THEN
889         WRITE(nulprt,*) subname, ' done prism_part_readgrid '
890         CALL oasis_flush(nulprt)
891      ENDIF
892      IF (OASIS_debug >= 2)  THEN
893          CALL oasis_mem_print(nulprt,subname//':part_readgrid')
894      ENDIF
895      if (local_timers_on) call oasis_timer_stop('oasis_enddef_part_readgrid')
896
897      !------------------------
898      !>   * Call advance_init to initialize coupling fields from restarts
899      !------------------------
900
901      if (local_timers_on) call oasis_timer_start('oasis_enddef_advance_init')
902      call oasis_advance_init(lkinfo)
903      IF (OASIS_debug >= 2)  THEN
904         WRITE(nulprt,*) subname, ' done prism_advance_init '
905         CALL oasis_flush(nulprt)
906      ENDIF
907      IF (OASIS_debug >= 2)  THEN
908          CALL oasis_mem_print(nulprt,subname//':advance_init')
909      ENDIF
910      if (local_timers_on) call oasis_timer_stop('oasis_enddef_advance_init')
911
912   elseif (ET_debug) then
913
914      WRITE(nulprt,*) ' load balancing special allocate for uncoupled components'
915      CALL flush(nulprt)
916
917      CALL oasis_lb_allocate(0)
918
919   endif   !  (mpi_comm_local /= MPI_COMM_NULL)
920
921   !--- Force OASIS_OK here rather than anything else ---
922
923   if (local_timers_on) call oasis_timer_start('oasis_enddef_last')
924   if (present(kinfo)) then
925      kinfo = OASIS_OK
926   endif
927   if (ET_debug) CALL oasis_lb_measure(-1,LB_ENDF)
928   CALL oasis_timer_stop ('oasis_enddef')
929   call oasis_timer_stop('init_thru_enddef')
930
931   IF (OASIS_debug >= 2)  THEN
932       CALL oasis_mem_print(nulprt,subname//':end')
933   ENDIF
934   if (local_timers_on) call oasis_timer_stop('oasis_enddef_last')
935
936   call oasis_debug_exit(subname)
937
938 END SUBROUTINE oasis_enddef
939!----------------------------------------------------------------------
940
941!> Local method to compute each models' global task ids, exists for reuse in enddef
942
943 SUBROUTINE mod_oasis_setrootglobal()
944
945   INTEGER(kind=ip_intwp_p) :: n, ierr
946   INTEGER(kind=ip_intwp_p),ALLOCATABLE :: tmparr(:)
947   character(len=*),parameter :: subname = '(oasis_setrootglobal)'
948
949   !------------------------
950   !--- set mpi_root_global
951   !------------------------
952
953   if (allocated(mpi_root_global)) then
954      deallocate(mpi_root_global)
955   endif
956   allocate(mpi_root_global(prism_amodels))
957   allocate(tmparr(prism_amodels))
958   tmparr = -1
959   do n = 1,prism_amodels
960      if (compid == n .and. mpi_rank_local == mpi_root_local) then
961         tmparr(n) = mpi_rank_global
962      endif
963   enddo
964   call oasis_mpi_max(tmparr,mpi_root_global,mpi_comm_global, &
965      string=subname//':mpi_root_global',all=.true.)
966   deallocate(tmparr)
967
968   do n = 1,prism_amodels
969      IF (mpi_root_global(n) < 0) THEN
970         WRITE(nulprt,*) subname,estr,'global root invalid, check couplcomm for active tasks'
971         call oasis_abort(file=__FILE__,line=__LINE__)
972      ENDIF
973   enddo
974
975   !------------------------
976   !--- set mpi_comp_size
977   !------------------------
978
979   if (allocated(mpi_comp_size)) then
980      deallocate(mpi_comp_size)
981   endif
982   allocate(mpi_comp_size(prism_amodels))
983   allocate(tmparr(prism_amodels))
984   tmparr = 0
985   tmparr(compid) = mpi_size_local
986   call oasis_mpi_max(tmparr,mpi_comp_size,mpi_comm_global, &
987      string=subname//':mpi_comp_size',all=.true.)
988   deallocate(tmparr)
989
990   do n = 1,prism_amodels
991      IF (mpi_comp_size(n) < 1) THEN
992         WRITE(nulprt,*) subname,estr,'comp size invalid, check couplcomm for active tasks'
993         call oasis_abort(file=__FILE__,line=__LINE__)
994      ENDIF
995   enddo
996
997END SUBROUTINE mod_oasis_setrootglobal
998!----------------------------------------------------------------------
999
1000END MODULE mod_oasis_method
Note: See TracBrowser for help on using the repository browser.