SCALE-RM
scale_process.F90
Go to the documentation of this file.
1 !-------------------------------------------------------------------------------
15  !-----------------------------------------------------------------------------
16  !
17  !++ used modules
18  !
19  use mpi
20  use gtool_file, only: &
22  use scale_precision
23  use scale_stdio
24  !-----------------------------------------------------------------------------
25  implicit none
26  private
27  !-----------------------------------------------------------------------------
28  !
29  !++ Public procedure
30  !
31  public :: prc_mpistart
32  public :: prc_universal_setup
33  public :: prc_global_setup
34  public :: prc_local_setup
35  public :: prc_mpistop
36  public :: prc_mpifinish
37  public :: prc_mpisplit
38  public :: prc_mpisplit_letkf
39 
40  public :: prc_mpibarrier
41  public :: prc_mpitime
42  public :: prc_mpitimestat
43 
44  !-----------------------------------------------------------------------------
45  !
46  !++ Public parameters & variables
47  !
48  !-----------------------------------------------------------------------------
49  ! [ communicator system ]
50  ! MPI_COMM_WORLD
51  ! |
52  ! PRC_UNIVERSAL_COMM_WORLD --split--> BULK_COMM_WORLD
53  ! |
54  ! PRC_GLOBAL_COMM_WORLD --split--> PRC_LOCAL_COMM_WORLD
55  !-----------------------------------------------------------------------------
56  integer, public, parameter :: prc_masterrank = 0
57  integer, public, parameter :: prc_domain_nlim = 10000
58 
59  ! universal world
60  integer, public :: prc_universal_comm_world = -1
61  integer, public :: prc_universal_myrank = -1
62  integer, public :: prc_universal_nprocs = -1
63  logical, public :: prc_universal_ismaster = .false.
64 
65  integer, public :: prc_universal_jobid = 0
66 
67  ! global world
68  integer, public :: prc_global_comm_world = -1
69  integer, public :: prc_global_myrank = -1
70  integer, public :: prc_global_nprocs = -1
71  logical, public :: prc_global_ismaster = .false.
72 
73  integer, public :: prc_global_domainid = 0
74 
75  ! local world
76  integer, public :: prc_local_comm_world = -1
77  integer, public :: prc_nprocs = 1
78  integer, public :: prc_myrank = 0
79  logical, public :: prc_ismaster = .false.
80 
81  ! error handling
82  logical, public :: prc_mpi_alive = .false.
83  integer, public :: prc_universal_handler
84  integer, public :: prc_abort_comm_world
85  integer, public :: prc_abort_handler
86 
87  !-----------------------------------------------------------------------------
88  !
89  !++ Private procedure
90  !
91  private :: prc_mpicoloring
92  private :: prc_sort_ascd
93 
94  !-----------------------------------------------------------------------------
95  !
96  !++ Private parameters & variables
97  !
98  integer, private, parameter :: prc_abort_code = -1
99 ! integer, private, parameter :: PRC_ABORT_code_p = 2 !< mpi abort code in error handler from parent
100 ! integer, private, parameter :: PRC_ABORT_code_d = 3 !< mpi abort code in error handler from daughter
101 
102  !-----------------------------------------------------------------------------
103 contains
104  !-----------------------------------------------------------------------------
106  subroutine prc_mpistart( &
107  comm )
108  implicit none
109 
110  integer, intent(out) :: comm ! communicator
111 
112  integer :: ierr
113  !---------------------------------------------------------------------------
114 
115  call mpi_init(ierr)
116 
117  prc_mpi_alive = .true.
118  prc_universal_handler = mpi_errhandler_null
119  call mpi_comm_create_errhandler( prc_mpi_errorhandler, prc_universal_handler, ierr )
120 
121  comm = mpi_comm_world
122 
123  return
124  end subroutine prc_mpistart
125 
126  !-----------------------------------------------------------------------------
128  subroutine prc_universal_setup( &
129  comm, &
130  nprocs, &
131  ismaster )
132  implicit none
133 
134  integer, intent(in) :: comm ! communicator
135  integer, intent(out) :: nprocs ! number of procs in this communicator
136  logical, intent(out) :: ismaster ! master process in this communicator?
137 
138  integer :: ierr
139  !---------------------------------------------------------------------------
140 
142 
143  call mpi_comm_size(prc_universal_comm_world,prc_universal_nprocs,ierr)
144  call mpi_comm_rank(prc_universal_comm_world,prc_universal_myrank,ierr)
145 
146  if ( prc_universal_myrank == prc_masterrank ) then
147  prc_universal_ismaster = .true.
148  else
149  prc_universal_ismaster = .false.
150  endif
151 
152  nprocs = prc_universal_nprocs
153  ismaster = prc_universal_ismaster
154 
155 
156 
158 
159  call mpi_comm_set_errhandler(prc_abort_comm_world,prc_universal_handler,ierr)
160  call mpi_comm_get_errhandler(prc_abort_comm_world,prc_abort_handler ,ierr)
161 
162  return
163  end subroutine prc_universal_setup
164 
165  !-----------------------------------------------------------------------------
167  subroutine prc_global_setup( &
168  abortall, &
169  comm )
170  implicit none
171 
172  logical, intent(in) :: abortall ! abort all jobs?
173  integer, intent(in) :: comm ! communicator
174 
175  integer :: ierr
176  !---------------------------------------------------------------------------
177 
178  prc_global_comm_world = comm
179 
180  call mpi_comm_size(prc_global_comm_world,prc_global_nprocs,ierr)
181  call mpi_comm_rank(prc_global_comm_world,prc_global_myrank,ierr)
182 
183  if ( prc_global_myrank == prc_masterrank ) then
184  prc_global_ismaster = .true.
185  else
186  prc_global_ismaster = .false.
187  endif
188 
189 ! if ( .NOT. abortall ) then
190 ! PRC_ABORT_COMM_WORLD = PRC_GLOBAL_COMM_WORLD
191 !
192 ! call MPI_COMM_SET_ERRHANDLER(PRC_ABORT_COMM_WORLD,PRC_UNIVERSAL_handler,ierr)
193 ! call MPI_COMM_GET_ERRHANDLER(PRC_ABORT_COMM_WORLD,PRC_ABORT_handler ,ierr)
194 ! endif
195 
196  return
197  end subroutine prc_global_setup
198 
199  !-----------------------------------------------------------------------------
201  subroutine prc_local_setup( &
202  comm, &
203  myrank, &
204  ismaster )
205  implicit none
206 
207  integer, intent(in) :: comm ! communicator
208  integer, intent(out) :: myrank ! myrank in this communicator
209  logical, intent(out) :: ismaster ! master process in this communicator?
210 
211  integer :: ierr
212  !---------------------------------------------------------------------------
213 
214  prc_local_comm_world = comm
215 
216  call mpi_comm_rank(prc_local_comm_world,prc_myrank,ierr)
217  call mpi_comm_size(prc_local_comm_world,prc_nprocs,ierr)
218 
219  if ( prc_myrank == prc_masterrank ) then
220  prc_ismaster = .true.
221  else
222  prc_ismaster = .false.
223  endif
224 
225  myrank = prc_myrank
226  ismaster = prc_ismaster
227 
228  return
229  end subroutine prc_local_setup
230 
231  !-----------------------------------------------------------------------------
233  subroutine prc_mpistop
234  implicit none
235 
236  integer :: ierr
237  !---------------------------------------------------------------------------
238 
239  if ( prc_mpi_alive ) then
240  ! tentative approach; input "PRC_UNIVERSAL_COMM_WORLD".
241  call mpi_comm_call_errhandler(prc_universal_comm_world,prc_abort_code,ierr)
242  endif
243 
244  stop
245  end subroutine prc_mpistop
246 
247  !-----------------------------------------------------------------------------
249  subroutine prc_mpifinish
250  implicit none
251 
252  integer :: ierr
253  !---------------------------------------------------------------------------
254 
255  if (prc_universal_handler .NE. mpi_errhandler_null) then
256  call mpi_errhandler_free(prc_universal_handler, ierr)
257  endif
258  if (prc_abort_handler .NE. mpi_errhandler_null) then
259  call mpi_errhandler_free(prc_abort_handler, ierr)
260  endif
261 
262  ! Stop MPI
263  if ( prc_mpi_alive ) then
264  if ( io_l ) then
265  write(io_fid_log,*)
266  write(io_fid_log,*) '++++++ Stop MPI'
267  write(io_fid_log,*)
268  endif
269 
270  ! free splitted communicator
272  call mpi_comm_free(prc_local_comm_world,ierr)
273  endif
274 
275  call mpi_barrier(prc_universal_comm_world,ierr)
276 
277  call mpi_finalize(ierr)
278  if( io_l ) write(io_fid_log,*) '*** MPI is peacefully finalized'
279  endif
280 
281  ! Close logfile, configfile
282  if ( io_l ) then
283  if( io_fid_log /= io_fid_stdout ) close(io_fid_log)
284  endif
285  close(io_fid_conf)
286 
287  ! Stop program
288  stop
289  end subroutine prc_mpifinish
290 
291  !-----------------------------------------------------------------------------
293  subroutine prc_mpisplit( &
294  ORG_COMM, & ! [in ]
295  NUM_DOMAIN, & ! [in ]
296  PRC_DOMAINS, & ! [in ]
297  CONF_FILES, & ! [in ]
298  LOG_SPLIT, & ! [in ]
299  bulk_split, & ! [in ]
300  color_reorder, & ! [in ]
301  INTRA_COMM, & ! [out]
302  inter_parent, & ! [out]
303  inter_child, & ! [out]
304  fname_local ) ! [out]
305  implicit none
306 
307  integer, intent(in) :: ORG_COMM
308  integer, intent(in) :: NUM_DOMAIN
309  integer, intent(in) :: PRC_DOMAINS(:)
310  character(len=H_LONG), intent(in) :: CONF_FILES(:)
311  logical, intent(in) :: LOG_SPLIT
312  logical, intent(in) :: bulk_split
313  logical, intent(in) :: color_reorder
314 
315  integer, intent(out) :: intra_comm
316  integer, intent(out) :: inter_parent
317  integer, intent(out) :: inter_child
318  character(len=H_LONG), intent(out) :: fname_local
319 
320  integer :: PARENT_COL(prc_domain_nlim) ! parent color number
321  integer :: CHILD_COL(prc_domain_nlim) ! child color number
322  integer :: PRC_ROOT(0:prc_domain_nlim) ! root process in the color
323  integer, allocatable :: COLOR_LIST(:) ! member list in each color
324  integer, allocatable :: KEY_LIST(:) ! local process number in each color
325 
326  integer :: total_nmax
327  integer :: ORG_myrank ! my rank number in the original communicator
328  integer :: ORG_nmax ! total rank number in the original communicator
329 
330  logical :: do_create_p(prc_domain_nlim)
331  logical :: do_create_c(prc_domain_nlim)
332  logical :: reordering
333 
334  character(len=H_LONG) :: COL_FILE(0:prc_domain_nlim)
335  character(len=4) :: col_num
336 
337  integer :: i
338  integer :: itag, ierr
339  !---------------------------------------------------------------------------
340 
341  intra_comm = org_comm
342  inter_parent = mpi_comm_null
343  inter_child = mpi_comm_null
344  fname_local = conf_files(1)
345 
346  if ( num_domain > 1 ) then ! multi domain run
347  call mpi_comm_rank(org_comm,org_myrank,ierr)
348  call mpi_comm_size(org_comm,org_nmax, ierr)
349  allocate ( color_list(0:org_nmax-1) )
350  allocate ( key_list(0:org_nmax-1) )
351 
352  total_nmax = 0
353  do i = 1, num_domain
354  total_nmax = total_nmax + prc_domains(i)
355  enddo
356  if ( total_nmax /= org_nmax ) then
357  if ( prc_universal_ismaster ) write (*,*) ""
358  if ( prc_universal_ismaster ) write (*,*) "ERROR: MPI PROCESS NUMBER is INCONSISTENT"
359  if ( prc_universal_ismaster ) write (*,*) "REQUESTED NPROCS = ", total_nmax, " LAUNCHED NPROCS = ", org_nmax
360  call prc_mpistop
361  endif
362 
363  reordering = color_reorder
364  if ( bulk_split ) then
365  reordering = .false.
366  endif
367  call prc_mpicoloring( org_comm, & ! [in ]
368  num_domain, & ! [in ]
369  prc_domains, & ! [in ]
370  conf_files, & ! [in ]
371  reordering, & ! [in ]
372  log_split, & ! [in ]
373  color_list, & ! [out]
374  prc_root, & ! [out]
375  key_list, & ! [out]
376  parent_col, & ! [out]
377  child_col, & ! [out]
378  col_file ) ! [out]
379 
380 
381  ! split comm_world
382  call mpi_comm_split(org_comm, &
383  color_list(org_myrank), &
384  key_list(org_myrank), &
385  intra_comm, ierr)
386  if ( bulk_split ) then
387  write(col_num,'(I4.4)') color_list(org_myrank)
388  fname_local = col_num
389  prc_universal_jobid = color_list(org_myrank)
390  else
391  fname_local = col_file(color_list(org_myrank))
392  endif
393 
394  ! set parent-child relationship
395  do_create_p(:) = .false.
396  do_create_c(:) = .false.
397  if ( .NOT. bulk_split ) then
398  do i = 1, num_domain-1
399  if ( prc_universal_ismaster ) write ( *, '(1X,A,I4)' ) "relationship: ", i
400  if ( prc_universal_ismaster ) write ( *, '(1X,A,I4,A,I4)' ) &
401  "--- parent color = ", parent_col(i), " child color = ", child_col(i)
402  if ( color_list(org_myrank) == parent_col(i) ) then
403  do_create_p(i) = .true.
404  elseif ( color_list(org_myrank) == child_col(i) ) then
405  do_create_c(i) = .true.
406  endif
407  enddo
408  endif
409 
410  ! create inter-commnunicator
411  inter_parent = mpi_comm_null
412  inter_child = mpi_comm_null
413  if ( .NOT. bulk_split ) then
414  do i = 1, num_domain-1
415  itag = i*100
416  if ( do_create_p(i) ) then ! as a parent
417  call mpi_intercomm_create( intra_comm, prc_masterrank, &
418  org_comm, prc_root(child_col(i)), &
419  itag, inter_child, ierr)
420  elseif ( do_create_c(i) ) then ! as a child
421  call mpi_intercomm_create( intra_comm, prc_masterrank, &
422  org_comm, prc_root(parent_col(i)), &
423  itag, inter_parent, ierr)
424  endif
425  call mpi_barrier(org_comm, ierr)
426  enddo
427  endif
428 
429  deallocate ( color_list, key_list )
430 
431  elseif ( num_domain == 1 ) then ! single domain run
432  if ( prc_universal_ismaster ) write (*,*) "*** a single comunicator"
433  else
434  if ( prc_universal_ismaster ) write (*,*) "ERROR: REQUESTED DOMAIN NUMBER IS NOT ACCEPTABLE"
435  call prc_mpistop
436  endif
437 
438  return
439  end subroutine prc_mpisplit
440 
441  !-----------------------------------------------------------------------------
443  subroutine prc_mpisplit_letkf( &
444  ORG_COMM, & ! [in ]
445  mem_np, & ! [in ]
446  nitmax, & ! [in ]
447  nprocs, & ! [in ]
448  proc2mem, & ! [in ]
449  INTRA_COMM ) ! [out]
450  implicit none
451 
452  integer, intent(in) :: ORG_COMM
453  integer, intent(in) :: mem_np
454  integer, intent(in) :: nitmax
455  integer, intent(in) :: nprocs
456  integer, intent(in) :: proc2mem(2,nitmax,nprocs)
457  integer, intent(out) :: intra_comm
458 
459  integer :: ORG_myrank ! my rank number in the original communicator
460  integer :: color, key
461  integer :: ierr
462  !---------------------------------------------------------------------------
463 
464  call mpi_comm_rank( org_comm, org_myrank, ierr)
465 
466  if ( proc2mem(1,1,org_myrank+1) >= 1 ) then
467  color = proc2mem(1,1,org_myrank+1) - 1
468  key = proc2mem(2,1,org_myrank+1)
469  else
470  color = mpi_undefined
471  key = mpi_undefined
472  end if
473 
474  call mpi_comm_split( org_comm, &
475  color, &
476  key, &
477  intra_comm, ierr )
478 
479  return
480  end subroutine prc_mpisplit_letkf
481 
482  !-----------------------------------------------------------------------------
484  subroutine prc_mpicoloring( &
485  ORG_COMM, & ! [in ]
486  NUM_DOMAIN, & ! [in ]
487  PRC_DOMAINS, & ! [in ]
488  CONF_FILES, & ! [in ]
489  color_reorder, & ! [in ]
490  LOG_SPLIT, & ! [in ]
491  COLOR_LIST, & ! [out]
492  PRC_ROOT, & ! [out]
493  KEY_LIST, & ! [out]
494  PARENT_COL, & ! [out]
495  CHILD_COL, & ! [out]
496  COL_FILE ) ! [out]
497  implicit none
498 
499  integer, intent(in) :: ORG_COMM
500  integer, intent(in) :: NUM_DOMAIN
501  integer, intent(in) :: PRC_DOMAINS(:)
502  character(len=H_LONG), intent(in) :: CONF_FILES(:)
503  logical, intent(in) :: color_reorder
504  logical, intent(in) :: LOG_SPLIT
505  integer, intent(out) :: COLOR_LIST(:) ! member list in each color
506  integer, intent(out) :: PRC_ROOT(0:prc_domain_nlim) ! root process in each color
507  integer, intent(out) :: KEY_LIST(:) ! local process number in each color
508  integer, intent(out) :: PARENT_COL(:) ! parent color number
509  integer, intent(out) :: CHILD_COL(:) ! child color number
510  character(len=H_LONG), intent(out) :: COL_FILE(0:prc_domain_nlim) ! conf file in each color
511 
512  integer :: touch(prc_domain_nlim)
513  integer :: PRC_ORDER(prc_domain_nlim) ! reordered number of process
514  integer :: ORDER2DOM(prc_domain_nlim) ! get domain number by order number
515  integer :: DOM2ORDER(prc_domain_nlim) ! get order number by domain number
516  integer :: DOM2COL(prc_domain_nlim) ! get color number by domain number
517  integer :: COL2DOM(0:prc_domain_nlim) ! get domain number by color number
518  integer :: RO_PRC_DOMAINS(prc_domain_nlim) ! reordered values
519  integer :: RO_DOM2COL(prc_domain_nlim) ! reordered values
520  integer :: RO_PARENT_COL(prc_domain_nlim) ! reordered values
521  integer :: RO_CHILD_COL(prc_domain_nlim) ! reordered values
522  character(len=H_LONG) :: RO_CONF_FILES(prc_domain_nlim) ! reordered values
523 
524  integer :: ORG_nmax ! parent domain number
525  integer :: id_parent ! parent domain number
526  integer :: id_child ! child domain number
527  integer :: dnum, nprc, order, key
528  integer :: i, j
529  integer :: ierr
530  !---------------------------------------------------------------------------
531 
532  call mpi_comm_size(org_comm,org_nmax, ierr)
533 
534  if ( color_reorder ) then
535  !--- make color order
536  ! domain num is counted from 1
537  ! color num is counted from 0
538  touch(:) = -1
539  prc_order(:) = prc_domains(:)
540  call prc_sort_ascd( prc_order(1:num_domain), 1, num_domain )
541 
542  do i = 1, num_domain
543  do j = 1, num_domain
544  if ( prc_domains(i) == prc_order(j) .AND. touch(j) < 0 ) then
545  dom2col(i ) = j - 1 ! domain_num --> color_num
546  col2dom(dom2col(i)) = i ! color_num --> domain_num
547  touch(j) = 1
548  exit
549  endif
550  enddo
551  enddo
552 
553  parent_col(:) = -1
554  child_col(:) = -1
555  do i = 1, num_domain
556  id_parent = i - 1
557  id_child = i + 1
558 
559  if ( 1 <= id_parent .AND. id_parent <= num_domain ) then
560  parent_col(i) = dom2col(id_parent)
561  endif
562  if ( 1 <= id_child .AND. id_child <= num_domain ) then
563  child_col(i) = dom2col(id_child)
564  endif
565 
566  if ( prc_universal_ismaster .AND. log_split ) then
567  write( *, '(1X,A,I2,1X,A,I2,2(2X,A,I2))' ) &
568  "DOMAIN: ", i, "MY_COL: ", dom2col(i), &
569  "PARENT: COL= ", parent_col(i), "CHILD: COL= ", child_col(i)
570  endif
571  enddo
572 
573  !--- reorder following color order
574  do i = 1, num_domain
575  dnum = col2dom(i-1)
576  order2dom(i) = dnum
577  dom2order(dnum) = i
578  ro_prc_domains(i) = prc_domains(dnum)
579  ro_dom2col(dnum) = dom2col(dnum)
580  ro_conf_files(i) = conf_files(dnum)
581  ro_parent_col(i) = parent_col(dnum)
582  ro_child_col(i) = child_col(dnum)
583  enddo
584 
585  !--- set relationship by ordering of relationship number
586  parent_col(:) = -1
587  child_col(:) = -1
588  do i = 1, num_domain-1
589  parent_col(i) = ro_parent_col( dom2order(i+1) ) ! from child to parent
590  child_col(i) = ro_child_col( dom2order(i) ) ! from parent to child
591  enddo
592 
593  do i = 1, num_domain
594  if ( prc_universal_ismaster ) write ( *, * ) ""
595  if ( prc_universal_ismaster ) write ( *, '(1X,A,I2,A,I5)' ) "ORDER (",i,") -> DOMAIN: ", order2dom(i)
596  if ( prc_universal_ismaster ) write ( *, '(1X,A,I1,A,I5)' ) "NUM PRC_DOMAINS(",i,") = ", ro_prc_domains(i)
597  if ( prc_universal_ismaster ) write ( *, '(1X,A,I1,A,I3)' ) "MY COLOR(",i,") = ", ro_dom2col(order2dom(i))
598  if ( prc_universal_ismaster ) write ( *, '(1X,A,I1,A,I3)' ) "PARENT COLOR(",i,") = ", ro_parent_col(i)
599  if ( prc_universal_ismaster ) write ( *, '(1X,A,I1,A,I3)' ) "CHILD COLOR(",i,") = ", ro_child_col(i)
600  if ( prc_universal_ismaster ) write ( *, '(1X,A,I1,A,A)' ) "CONF_FILES(",i,") = ", trim(ro_conf_files(i))
601  enddo
602  if ( prc_universal_ismaster ) write ( *, * ) ""
603 
604  do i=1, num_domain
605  col_file(i-1) = ro_conf_files(i) ! final copy
606  enddo
607 
608  else !--- without reordering of colors
609  order2dom(:) = -1
610  ro_dom2col(:) = -1
611  ro_prc_domains(:) = -1
612  ro_prc_domains(:) = -1
613  ro_parent_col(:) = -1
614  ro_child_col(:) = -1
615 
616  do i = 1, num_domain
617  order2dom(i) = i
618  ro_dom2col(i) = i-1
619  ro_prc_domains(i) = prc_domains(i)
620  ro_conf_files(i) = conf_files(i)
621  enddo
622 
623  do i = 1, num_domain
624  id_parent = i - 1
625  id_child = i + 1
626 
627  if ( 1 <= id_parent .AND. id_parent <= num_domain ) then
628  ro_parent_col(i) = ro_dom2col(id_parent)
629  endif
630  if ( 1 <= id_child .AND. id_child <= num_domain ) then
631  ro_child_col(i) = ro_dom2col(id_child)
632  endif
633  enddo
634 
635  ! make relationship
636  do i = 1, num_domain-1
637  parent_col(i) = ro_parent_col(i+1) ! from child to parent
638  child_col(i) = ro_child_col(i ) ! from parent to child
639  enddo
640 
641  endif
642 
643  ! make a process table
644  order = 1
645  key = 0
646  nprc = ro_prc_domains(order)
647  prc_root(:) = -999
648 
649  do i = 0, org_nmax-1
650  color_list(i+1) = ro_dom2col(order2dom(order))
651  key_list(i+1) = key
652  if ( key == 0 ) then
653  prc_root(color_list(i+1)) = i
654  col_file(color_list(i+1)) = ro_conf_files(order)
655  endif
656  if ( log_split .AND. prc_universal_ismaster ) then
657  write ( *, '(1X,4(A,I5))' ) "PE:", i, " COLOR:", color_list(i+1), &
658  " KEY:", key_list(i+1), " PRC_ROOT:", prc_root(color_list(i+1))
659  endif
660  key = key + 1
661  if ( key >= nprc ) then
662  order = order + 1
663  key = 0
664  nprc = ro_prc_domains(order)
665  endif
666  enddo
667 
668  return
669  end subroutine prc_mpicoloring
670  !-----------------------------------------------------------------------------
671 
672  !-----------------------------------------------------------------------------
674  recursive subroutine prc_sort_ascd(a, top, bottom)
675  implicit none
676  integer, intent(inout) :: a(:)
677  integer, intent(in) :: top, bottom
678  integer :: i, j, cnt, trg
679  !---------------------------------------------------------------------------
680  cnt = a( (top+bottom) / 2 )
681  i = top; j = bottom
682  do
683  do while ( a(i) > cnt ) !ascending evaluation
684  i = i + 1
685  enddo
686  do while ( cnt > a(j) ) !ascending evaluation
687  j = j - 1
688  enddo
689  if ( i >= j ) exit
690  trg = a(i); a(i) = a(j); a(j) = trg
691  i = i + 1
692  j = j - 1
693  enddo
694  if ( top < i-1 ) call prc_sort_ascd( a, top, i-1 )
695  if ( j+1 < bottom ) call prc_sort_ascd( a, j+1, bottom )
696  return
697  end subroutine prc_sort_ascd
698  !-----------------------------------------------------------------------------
699 
700  !-----------------------------------------------------------------------------
702  subroutine prc_mpibarrier
703  implicit none
704 
705  integer :: ierr
706  !---------------------------------------------------------------------------
707 
708  if ( prc_mpi_alive ) then
709  call mpi_barrier(prc_local_comm_world,ierr)
710  endif
711 
712  end subroutine prc_mpibarrier
713 
714  !-----------------------------------------------------------------------------
717  function prc_mpitime() result(time)
718  implicit none
719 
720  real(DP) :: time
721  !---------------------------------------------------------------------------
722 
723  if ( prc_mpi_alive ) then
724  time = real(MPI_WTIME(), kind=dp)
725  else
726  call cpu_time(time)
727  endif
728 
729  end function prc_mpitime
730 
731  !-----------------------------------------------------------------------------
733  subroutine prc_mpitimestat( &
734  avgvar, &
735  maxvar, &
736  minvar, &
737  maxidx, &
738  minidx, &
739  var )
740  implicit none
741 
742  real(DP), intent(out) :: avgvar(:)
743  real(DP), intent(out) :: maxvar(:)
744  real(DP), intent(out) :: minvar(:)
745  integer, intent(out) :: maxidx(:)
746  integer, intent(out) :: minidx(:)
747  real(DP), intent(in) :: var(:)
748 
749  real(DP), allocatable :: statval(:,:)
750  integer :: vsize
751 
752  real(DP) :: totalvar
753  integer :: ierr
754  integer :: v, p
755  !---------------------------------------------------------------------------
756 
757  vsize = size(var(:))
758 
759  allocate( statval(vsize,0:prc_nprocs-1) )
760  statval(:,:) = 0.0_dp
761 
762  do v = 1, vsize
763  statval(v,prc_myrank) = var(v)
764  enddo
765 
766  ! MPI broadcast
767  do p = 0, prc_nprocs-1
768  call mpi_bcast( statval(1,p), &
769  vsize, &
770  mpi_double_precision, &
771  p, &
773  ierr )
774  enddo
775 
776  do v = 1, vsize
777  totalvar = 0.0_dp
778  do p = 0, prc_nprocs-1
779  totalvar = totalvar + statval(v,p)
780  enddo
781  avgvar(v) = totalvar / prc_nprocs
782 
783  maxvar(v) = maxval(statval(v,:))
784  minvar(v) = minval(statval(v,:))
785  maxidx(v:v) = maxloc(statval(v,:))
786  minidx(v:v) = minloc(statval(v,:))
787  enddo
788 
789  deallocate( statval )
790 
791  return
792  end subroutine prc_mpitimestat
793 
794  !-----------------------------------------------------------------------------
796  subroutine prc_mpi_errorhandler( &
797  comm, &
798  errcode )
799  implicit none
800 
801  ! attributes are needed to be the same with COMM_ERRHANDLER function
802  integer :: comm
803  integer :: errcode
804 
805  character(len=MPI_MAX_ERROR_STRING) :: msg
806  integer :: len
807  integer :: ierr
808  !---------------------------------------------------------------------------
809 
810  ! Print Error Messages
811  if ( prc_mpi_alive ) then
812  ! flush 1kbyte
813  if ( io_l ) then
814  write(io_fid_log,'(32A32)') ' '
815  write(io_fid_log,*) '++++++ Abort MPI'
816  write(io_fid_log,*) ''
817  end if
818 
819  if ( io_l ) then
820  write(*,*) '++++++ BULK ID: ',prc_universal_jobid
821  write(*,*) '++++++ DOMAIN ID: ',prc_global_domainid
822  write(*,*) '++++++ MASTER LOCATION: ',prc_universal_myrank,'/',prc_universal_nprocs
823  write(*,*) '++++++ GLOBAL LOCATION: ',prc_global_myrank,'/',prc_global_nprocs
824  write(*,*) '++++++ LOCAL LOCATION: ',prc_myrank,'/',prc_nprocs
825  write(*,*) ''
826  end if
827 
828  if ( errcode == prc_abort_code ) then ! called from PRC_MPIstop
829  elseif ( errcode <= mpi_err_lastcode ) then
830  call mpi_error_string(errcode, msg, len, ierr)
831  if ( io_l ) write(io_fid_log,*) '++++++ ', errcode, trim(msg)
832  write(*,*) '++++++ ', errcode, trim(msg)
833  else
834  if ( io_l ) write(io_fid_log,*) '++++++ Unexpected error code', errcode
835  write(*,*) '++++++ Unexpected error code', errcode
836  endif
837 
838  if ( comm /= prc_abort_comm_world ) then
839  if ( io_l ) write(io_fid_log,*) '++++++ Unexpected communicator'
840  write(*,*) '++++++ Unexpected communicator'
841  endif
842  if ( io_l ) write(io_fid_log,*) ''
843  write(*,*) ''
844  endif
845 
846  call filecloseall
847 
848  ! Close logfile, configfile
849  if ( io_l ) then
850  if ( io_fid_log /= io_fid_stdout ) close(io_fid_log)
851  endif
852  close(io_fid_conf)
853 
854  ! Abort MPI
855  if ( prc_mpi_alive ) then
856  call sleep(5)
857  call mpi_abort(prc_abort_comm_world, prc_abort_code, ierr)
858  endif
859 
860  stop
861  end subroutine prc_mpi_errorhandler
862 
863 end module scale_process
864 !-------------------------------------------------------------------------------
module GTOOL_FILE
Definition: gtool_file.f90:17
logical, public prc_ismaster
master process in local communicator?
integer, public prc_local_comm_world
local communicator
subroutine, public prc_mpistop
Abort MPI.
logical, public prc_mpi_alive
MPI is alive?
logical, public prc_global_ismaster
master process in global communicator?
logical, public io_l
output log or not? (this process)
Definition: scale_stdio.F90:59
module STDIO
Definition: scale_stdio.F90:12
integer, public prc_universal_nprocs
process num in universal communicator
integer, parameter, public io_fid_stdout
Definition: scale_stdio.F90:54
subroutine, public prc_universal_setup(comm, nprocs, ismaster)
setup MPI in universal communicator
subroutine, public prc_mpisplit(ORG_COMM, NUM_DOMAIN, PRC_DOMAINS, CONF_FILES, LOG_SPLIT, bulk_split, color_reorder, INTRA_COMM, inter_parent, inter_child, fname_local)
MPI Communicator Split.
integer, public prc_universal_comm_world
original communicator
subroutine, public filecloseall
integer, public prc_universal_handler
error handler in universal communicator
logical, public prc_universal_ismaster
master process in universal communicator?
subroutine, public prc_mpitimestat(avgvar, maxvar, minvar, maxidx, minidx, var)
Calc global statistics for timer.
integer, parameter, public dp
Definition: dc_types.f90:27
subroutine, public prc_mpisplit_letkf(ORG_COMM, mem_np, nitmax, nprocs, proc2mem, INTRA_COMM)
MPI Communicator Split for SCALE-LETKF ensemble.
integer, public prc_global_comm_world
global communicator
real(dp) function, public prc_mpitime()
Get MPI time.
module PROCESS
subroutine, public prc_global_setup(abortall, comm)
setup MPI in global communicator
integer, public prc_global_myrank
myrank in global communicator
subroutine, public prc_mpistart(comm)
Start MPI.
integer, parameter, public prc_masterrank
master process in each communicator
integer, public prc_myrank
process num in local communicator
integer, public prc_abort_handler
error handler communicator for aborting
integer, public prc_global_nprocs
process num in global communicator
module PRECISION
integer, public prc_abort_comm_world
communicator for aborting
integer, parameter, public prc_domain_nlim
max depth of domains
integer, public prc_universal_jobid
my job ID in universal communicator
subroutine, public prc_local_setup(comm, myrank, ismaster)
Setup MPI.
integer, public io_fid_conf
Config file ID.
Definition: scale_stdio.F90:55
integer, public prc_global_domainid
my domain ID in global communicator
integer, public prc_universal_myrank
myrank in universal communicator
subroutine, public prc_mpibarrier
Barrier MPI.
integer, public io_fid_log
Log file ID.
Definition: scale_stdio.F90:56
integer, public prc_nprocs
myrank in local communicator
subroutine, public prc_mpifinish
Stop MPI peacefully.