source: palm/trunk/SOURCE/pmc_handle_communicator_mod.f90 @ 4649

Last change on this file since 4649 was 4649, checked in by raasch, 4 years ago

files re-formatted to follow the PALM coding standard

  • Property svn:keywords set to Id
File size: 19.5 KB
Line 
1!> @file pmc_handle_communicator_mod.f90
2!--------------------------------------------------------------------------------------------------!
3! This file is part of the PALM model system.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2020 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------------------------!
18!
19!
20! Current revisions:
21! -----------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: pmc_handle_communicator_mod.f90 4649 2020-08-25 12:11:17Z raasch $
27! File re-formatted to follow the PALM coding standard
28!
29!
30! 4629 2020-07-29 09:37:56Z raasch
31! Support for MPI Fortran77 interface (mpif.h) removed
32!
33! 4360 2020-01-07 11:25:50Z suehring
34! Corrected "Former revisions" section
35!
36! 3888 2019-04-12 09:18:10Z hellstea
37! Missing MPI_BCAST of anterpolation_buffer_width added.
38!
39! 3885 2019-04-11 11:29:34Z kanani
40! Changes related to global restructuring of location messages and introduction of additional debug
41! messages
42!
43! 3819 2019-03-27 11:01:36Z hellstea
44! Adjustable anterpolation buffer introduced on all nest boundaries, it is controlled by the new
45! nesting_parameters parameter anterpolation_buffer_width.
46!
47! 3655 2019-01-07 16:51:22Z knoop
48! nestpar renamed to nesting_parameters
49!
50! 1762 2016-02-25 12:31:13Z hellstea
51! Initial revision by K. Ketelsen
52!
53! Description:
54! ------------
55! Handle MPI communicator in PALM model coupler
56!--------------------------------------------------------------------------------------------------!
57 MODULE PMC_handle_communicator
58#if defined( __parallel )
59    USE kinds
60
61    USE MPI
62
63    USE pmc_general,                                                                               &
64        ONLY: pmc_max_models,                                                                      &
65              pmc_status_error,                                                                    &
66              pmc_status_ok
67
68
69    USE control_parameters,                                                                        &
70        ONLY: message_string
71
72    IMPLICIT NONE
73
74
75    TYPE pmc_layout
76
77       CHARACTER(LEN=32) ::  name  !<
78
79       INTEGER ::  id            !<
80       INTEGER ::  npe_total     !<
81       INTEGER ::  parent_id     !<
82
83       REAL(wp) ::  lower_left_x  !<
84       REAL(wp) ::  lower_left_y  !<
85
86    END TYPE pmc_layout
87
88    PUBLIC  pmc_status_ok, pmc_status_error  !<
89
90    INTEGER, PARAMETER, PUBLIC ::  pmc_error_npes        = 1  !< illegal number of processes
91    INTEGER, PARAMETER, PUBLIC ::  pmc_namelist_error    = 2  !< error(s) in nesting_parameters namelist
92    INTEGER, PARAMETER, PUBLIC ::  pmc_no_namelist_found = 3  !< no couple layout namelist found
93
94    INTEGER ::  m_my_cpl_id   !< coupler id of this model
95    INTEGER ::  m_ncpl        !< number of couplers given in nesting_parameters namelist
96    INTEGER ::  m_parent_id   !< coupler id of parent of this model
97    INTEGER ::  m_world_comm  !< global nesting communicator
98
99    TYPE(pmc_layout), PUBLIC, DIMENSION(pmc_max_models) ::  m_couplers  !< information of all couplers
100
101    INTEGER, PUBLIC ::  m_model_comm          !< communicator of this model
102    INTEGER, PUBLIC ::  m_model_npes          !<
103    INTEGER, PUBLIC ::  m_model_rank          !<
104    INTEGER, PUBLIC ::  m_to_parent_comm      !< communicator to the parent
105    INTEGER, PUBLIC ::  m_world_rank          !<
106    INTEGER         ::  m_parent_remote_size  !< number of processes in the parent model
107    INTEGER         ::  m_world_npes          !<
108    INTEGER         ::  peer_comm             !< peer_communicator for inter communicators
109
110    INTEGER, DIMENSION(pmc_max_models), PUBLIC ::  m_to_child_comm   !< communicator to the child(ren)
111    INTEGER, DIMENSION(:), POINTER, PUBLIC ::  pmc_parent_for_child  !<
112
113
114    INTERFACE pmc_get_model_info
115       MODULE PROCEDURE pmc_get_model_info
116    END INTERFACE pmc_get_model_info
117
118    INTERFACE pmc_is_rootmodel
119       MODULE PROCEDURE pmc_is_rootmodel
120    END INTERFACE pmc_is_rootmodel
121
122    PUBLIC pmc_get_model_info, pmc_init_model, pmc_is_rootmodel   !<
123
124
125
126 CONTAINS
127
128
129!--------------------------------------------------------------------------------------------------!
130! Description:
131! ------------
132!> @Todo: Missing subroutine description.
133!--------------------------------------------------------------------------------------------------!
134 SUBROUTINE pmc_init_model( comm, nesting_datatransfer_mode, nesting_mode,                         &
135                            anterpolation_buffer_width, pmc_status )
136
137    USE control_parameters,                                                                        &
138        ONLY:  message_string
139
140    USE pegrid,                                                                                    &
141        ONLY:  myid
142
143      IMPLICIT NONE
144
145    CHARACTER(LEN=7), INTENT(INOUT) ::  nesting_datatransfer_mode  !<
146    CHARACTER(LEN=8), INTENT(INOUT) ::  nesting_mode               !<
147
148    INTEGER, INTENT(INOUT) ::  anterpolation_buffer_width  !< Boundary buffer width for anterpolation
149    INTEGER, INTENT(INOUT) ::  comm                        !<
150    INTEGER, INTENT(INOUT) ::  pmc_status                  !<
151
152    INTEGER ::  childcount     !<
153    INTEGER ::  i              !<
154    INTEGER ::  ierr           !<
155    INTEGER ::  istat          !<
156    INTEGER ::  m_my_cpl_rank  !<
157    INTEGER ::  tag            !<
158
159    INTEGER, DIMENSION(pmc_max_models)   ::  activeparent  !< I am active parent for this child ID
160    INTEGER, DIMENSION(pmc_max_models+1) ::  start_pe      !<
161
162    pmc_status   = pmc_status_ok
163    comm         = -1
164    m_world_comm = MPI_COMM_WORLD
165    m_my_cpl_id  = -1
166    childcount   =  0
167    activeparent = -1
168    start_pe(:)  =  0
169
170    CALL MPI_COMM_RANK( MPI_COMM_WORLD, m_world_rank, istat )
171    CALL MPI_COMM_SIZE( MPI_COMM_WORLD, m_world_npes, istat )
172!
173!-- Only process 0 of root model reads
174    IF ( m_world_rank == 0 )  THEN
175
176       CALL read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
177                                  anterpolation_buffer_width, pmc_status )
178
179       IF ( pmc_status /= pmc_no_namelist_found  .AND.                                             &
180            pmc_status /= pmc_namelist_error )                                                     &
181       THEN
182!
183!--       Calculate start PE of every model
184          start_pe(1) = 0
185          DO  i = 2, m_ncpl+1
186             start_pe(i) = start_pe(i-1) + m_couplers(i-1)%npe_total
187          ENDDO
188
189!
190!--       The sum of numbers of processes requested by all the domains must be equal to the total
191!--       number of processes of the run
192          IF ( start_pe(m_ncpl+1) /= m_world_npes )  THEN
193             WRITE( message_string, '(2A,I6,2A,I6,A)' )                                            &
194                                                'nesting-setup requires different number of ',     &
195                                                'MPI procs (', start_pe(m_ncpl+1), ') than ',      &
196                                                'provided (', m_world_npes,')'
197             CALL message( 'pmc_init_model', 'PA0229', 3, 2, 0, 6, 0 )
198          ENDIF
199
200       ENDIF
201
202    ENDIF
203!
204!-- Broadcast the read status. This synchronises all other processes with process 0 of the root
205!-- model. Without synchronisation, they would not behave in the correct way (e.g. they would not
206!-- return in case of a missing NAMELIST).
207    CALL MPI_BCAST( pmc_status, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, istat )
208
209    IF ( pmc_status == pmc_no_namelist_found )  THEN
210!
211!--    Not a nested run; return the MPI_WORLD communicator
212       comm = MPI_COMM_WORLD
213       RETURN
214
215    ELSEIF ( pmc_status == pmc_namelist_error )  THEN
216!
217!--    Only the root model gives the error message. Others are aborted by the message-routine with
218!--    MPI_ABORT. Must be done this way since myid and comm2d have not yet been assigned at this
219!--    point.
220       IF ( m_world_rank == 0 )  THEN
221          message_string = 'errors in \$nesting_parameters'
222          CALL message( 'pmc_init_model', 'PA0223', 3, 2, 0, 6, 0 )
223       ENDIF
224
225    ENDIF
226
227    CALL MPI_BCAST( m_ncpl,          1, MPI_INTEGER, 0, MPI_COMM_WORLD, istat )
228    CALL MPI_BCAST( start_pe, m_ncpl+1, MPI_INTEGER, 0, MPI_COMM_WORLD, istat )
229!
230!-- Broadcast coupling layout
231    DO  i = 1, m_ncpl
232       CALL MPI_BCAST( m_couplers(i)%name, LEN( m_couplers(i)%name ),                              &
233                       MPI_CHARACTER, 0, MPI_COMM_WORLD, istat )
234       CALL MPI_BCAST( m_couplers(i)%id,           1, MPI_INTEGER, 0,                              &
235                       MPI_COMM_WORLD, istat )
236       CALL MPI_BCAST( m_couplers(i)%Parent_id,    1, MPI_INTEGER, 0,                              &
237                       MPI_COMM_WORLD, istat )
238       CALL MPI_BCAST( m_couplers(i)%npe_total,    1, MPI_INTEGER, 0,                              &
239                       MPI_COMM_WORLD, istat )
240       CALL MPI_BCAST( m_couplers(i)%lower_left_x, 1, MPI_REAL,    0,                              &
241                       MPI_COMM_WORLD, istat )
242       CALL MPI_BCAST( m_couplers(i)%lower_left_y, 1, MPI_REAL,    0,                              &
243                       MPI_COMM_WORLD, istat )
244    ENDDO
245    CALL MPI_BCAST( nesting_mode, LEN( nesting_mode ), MPI_CHARACTER, 0, MPI_COMM_WORLD, istat )
246    CALL MPI_BCAST( nesting_datatransfer_mode, LEN(nesting_datatransfer_mode), MPI_CHARACTER, 0,   &
247                    MPI_COMM_WORLD, istat )
248    CALL MPI_BCAST( anterpolation_buffer_width, 1, MPI_INT, 0, MPI_COMM_WORLD, istat )
249!
250!-- Assign global MPI processes to individual models by setting the couple id
251    DO  i = 1, m_ncpl
252       IF ( m_world_rank >= start_pe(i)  .AND.  m_world_rank < start_pe(i+1) )  THEN
253          m_my_cpl_id = i
254          EXIT
255       ENDIF
256    ENDDO
257    m_my_cpl_rank = m_world_rank - start_pe(i)
258!
259!-- MPI_COMM_WORLD is the communicator for ALL models (MPI-1 approach). The communictors for the
260!-- individual models as created by MPI_COMM_SPLIT. The color of the model is represented by the
261!-- coupler id
262    CALL MPI_COMM_SPLIT( MPI_COMM_WORLD, m_my_cpl_id, m_my_cpl_rank, comm, istat )
263!
264!-- Get size and rank of the model running on this process
265    CALL  MPI_COMM_RANK( comm, m_model_rank, istat )
266    CALL  MPI_COMM_SIZE( comm, m_model_npes, istat )
267!
268!-- Broadcast (from process 0) the parent id and id of every model
269    DO  i = 1, m_ncpl
270       CALL MPI_BCAST( m_couplers(i)%parent_id, 1, MPI_INTEGER, 0, MPI_COMM_WORLD, istat )
271       CALL MPI_BCAST( m_couplers(i)%id,        1, MPI_INTEGER, 0, MPI_COMM_WORLD, istat )
272    ENDDO
273!
274!-- Save the current model communicator for pmc internal use
275    m_model_comm = comm
276
277!
278!-- Create intercommunicator between the parent and children.
279!-- MPI_INTERCOMM_CREATE creates an intercommunicator between 2 groups of different colors. The
280!-- grouping was done above with MPI_COMM_SPLIT. A duplicate of MPI_COMM_WORLD is created and used
281!-- as peer communicator (peer_comm) for MPI_INTERCOMM_CREATE.
282    CALL MPI_COMM_DUP( MPI_COMM_WORLD, peer_comm, ierr )
283    DO  i = 2, m_ncpl
284       IF ( m_couplers(i)%parent_id == m_my_cpl_id )  THEN
285!
286!--       Identify all children models of the current model and create inter-communicators to
287!--       connect between the current model and its children models.
288          tag = 500 + i
289          CALL MPI_INTERCOMM_CREATE( comm, 0, peer_comm, start_pe(i), tag, m_to_child_comm(i),     &
290                                     istat )
291          childcount = childcount + 1
292          activeparent(i) = 1
293       ELSEIF ( i == m_my_cpl_id)  THEN
294!
295!--       Create an inter-communicator to connect between the current model and its parent model.
296          tag = 500 + i
297          CALL MPI_INTERCOMM_CREATE( comm, 0, peer_comm, start_pe(m_couplers(i)%parent_id), tag,   &
298                                     m_to_parent_comm, istat )
299       ENDIF
300    ENDDO
301!
302!-- If I am a parent, count the number of children I have. Although this loop is symmetric on all
303!-- processes, the "activeparent" flag is true (==1) on the respective individual process only.
304    ALLOCATE( pmc_parent_for_child(childcount+1) )
305
306    childcount = 0
307    DO  i = 2, m_ncpl
308       IF ( activeparent(i) == 1 )  THEN
309          childcount = childcount + 1
310          pmc_parent_for_child(childcount) = i
311       ENDIF
312    ENDDO
313!
314!-- Get the size of the parent model
315    IF ( m_my_cpl_id > 1 )  THEN
316       CALL MPI_COMM_REMOTE_SIZE( m_to_parent_comm, m_parent_remote_size, istat )
317    ELSE
318!
319!--    The root model does not have a parent
320       m_parent_remote_size = -1
321    ENDIF
322!
323!-- Set myid to non-zero value except for the root domain. This is a setting for the message routine
324!-- which is called at the end of pmci_init. That routine outputs messages for myid = 0, only.
325!-- However, myid has not been assigened so far, so that all processes of the root model would
326!-- output a message. To avoid this, set myid to some other value except for process 0 of the root
327!-- domain.
328    IF ( m_world_rank /= 0 )  myid = 1
329
330 END SUBROUTINE PMC_init_model
331
332
333!--------------------------------------------------------------------------------------------------!
334! Description:
335! ------------
336!> @Todo: Missing subroutine description.
337!--------------------------------------------------------------------------------------------------!
338 SUBROUTINE pmc_get_model_info( comm_world_nesting, cpl_id, cpl_name, cpl_parent_id, lower_left_x, &
339                                lower_left_y, ncpl, npe_total, request_for_cpl_id )
340!
341!-- Provide module private variables of the pmc for PALM
342
343    USE kinds
344
345    IMPLICIT NONE
346
347    CHARACTER(LEN=*), INTENT(OUT), OPTIONAL ::  cpl_name   !<
348
349    INTEGER, INTENT(IN), OPTIONAL ::  request_for_cpl_id   !<
350
351    INTEGER, INTENT(OUT), OPTIONAL ::  comm_world_nesting  !<
352    INTEGER, INTENT(OUT), OPTIONAL ::  cpl_id              !<
353    INTEGER, INTENT(OUT), OPTIONAL ::  cpl_parent_id       !<
354    INTEGER, INTENT(OUT), OPTIONAL ::  ncpl                !<
355    INTEGER, INTENT(OUT), OPTIONAL ::  npe_total           !<
356
357    INTEGER ::  requested_cpl_id                           !<
358
359    REAL(wp), INTENT(OUT), OPTIONAL ::  lower_left_x       !<
360    REAL(wp), INTENT(OUT), OPTIONAL ::  lower_left_y       !<
361
362!
363!-- Set the requested coupler id
364    IF ( PRESENT( request_for_cpl_id ) )  THEN
365       requested_cpl_id = request_for_cpl_id
366!
367!--    Check for allowed range of values
368       IF ( requested_cpl_id < 1  .OR.  requested_cpl_id > m_ncpl )  RETURN
369    ELSE
370       requested_cpl_id = m_my_cpl_id
371    ENDIF
372!
373!-- Return the requested information
374    IF ( PRESENT( comm_world_nesting )  )  THEN
375       comm_world_nesting = m_world_comm
376    ENDIF
377    IF ( PRESENT( cpl_id )        )  THEN
378       cpl_id = requested_cpl_id
379    ENDIF
380    IF ( PRESENT( cpl_parent_id ) )  THEN
381       cpl_parent_id = m_couplers(requested_cpl_id)%parent_id
382    ENDIF
383    IF ( PRESENT( cpl_name )      )  THEN
384       cpl_name = m_couplers(requested_cpl_id)%name
385    ENDIF
386    IF ( PRESENT( ncpl )          )  THEN
387       ncpl = m_ncpl
388    ENDIF
389    IF ( PRESENT( npe_total )     )  THEN
390       npe_total = m_couplers(requested_cpl_id)%npe_total
391    ENDIF
392    IF ( PRESENT( lower_left_x )  )  THEN
393       lower_left_x = m_couplers(requested_cpl_id)%lower_left_x
394    ENDIF
395    IF ( PRESENT( lower_left_y )  )  THEN
396       lower_left_y = m_couplers(requested_cpl_id)%lower_left_y
397    ENDIF
398
399 END SUBROUTINE pmc_get_model_info
400
401
402
403 LOGICAL function pmc_is_rootmodel( )
404
405    IMPLICIT NONE
406
407    pmc_is_rootmodel = ( m_my_cpl_id == 1 )
408
409 END FUNCTION pmc_is_rootmodel
410
411
412
413!--------------------------------------------------------------------------------------------------!
414! Description:
415! ------------
416!> @Todo: Missing subroutine description.
417!--------------------------------------------------------------------------------------------------!
418 SUBROUTINE read_coupling_layout( nesting_datatransfer_mode, nesting_mode,                         &
419                                  anterpolation_buffer_width, pmc_status )
420
421    IMPLICIT NONE
422
423    CHARACTER(LEN=7), INTENT(INOUT) ::  nesting_datatransfer_mode  !<
424    CHARACTER(LEN=8), INTENT(INOUT) ::  nesting_mode               !<
425
426    INTEGER, INTENT(INOUT)      ::  anterpolation_buffer_width  !< Boundary buffer width for anterpolation
427    INTEGER(iwp), INTENT(INOUT) ::  pmc_status                  !<
428
429    INTEGER(iwp) ::  bad_llcorner  !<
430    INTEGER(iwp) ::  i             !<
431    INTEGER(iwp) ::  istat         !<
432
433    TYPE(pmc_layout), DIMENSION(pmc_max_models) ::  domain_layouts  !<
434
435    NAMELIST /nesting_parameters/  domain_layouts,                                                 &
436                                   nesting_datatransfer_mode,                                      &
437                                   nesting_mode,                                                   &
438                                   anterpolation_buffer_width
439
440!
441!-- Initialize some coupling variables
442    domain_layouts(1:pmc_max_models)%id = -1
443    m_ncpl =   0
444
445    pmc_status = pmc_status_ok
446!
447!-- Open the NAMELIST-file and read the nesting layout
448    CALL check_open( 11 )
449    READ ( 11, nesting_parameters, IOSTAT = istat )
450!
451!-- Set filepointer to the beginning of the file. Otherwise process 0 will later be unable to read
452!-- the inipar-NAMELIST
453    REWIND ( 11 )
454
455    IF ( istat < 0 )  THEN
456!
457!--    No nesting_parameters-NAMELIST found
458       pmc_status = pmc_no_namelist_found
459       RETURN
460    ELSEIF ( istat > 0 )  THEN
461!
462!--    Errors in reading nesting_parameters-NAMELIST
463       pmc_status = pmc_namelist_error
464       RETURN
465    ENDIF
466!
467!-- Output location message
468    CALL location_message( 'initialize communicators for nesting', 'start' )
469!
470!-- Assign the layout to the corresponding internally used variable m_couplers
471    m_couplers = domain_layouts
472!
473!-- Get the number of nested models given in the nesting_parameters-NAMELIST
474    DO  i = 1, pmc_max_models
475!
476!--    When id=-1 is found for the first time, the list of domains is finished
477       IF ( m_couplers(i)%id == -1  .OR.  i == pmc_max_models )  THEN
478          IF ( m_couplers(i)%id == -1 )  THEN
479             m_ncpl = i - 1
480             EXIT
481          ELSE
482             m_ncpl = pmc_max_models
483          ENDIF
484       ENDIF
485    ENDDO
486!
487!-- Make sure that all domains have equal lower left corner in case of vertical nesting
488    IF ( nesting_mode == 'vertical' )  THEN
489       bad_llcorner = 0
490       DO  i = 1, m_ncpl
491          IF ( domain_layouts(i)%lower_left_x /= 0.0_wp .OR.                                       &
492               domain_layouts(i)%lower_left_y /= 0.0_wp )  THEN
493             bad_llcorner = bad_llcorner + 1
494             domain_layouts(i)%lower_left_x = 0.0_wp
495             domain_layouts(i)%lower_left_y = 0.0_wp
496          ENDIF
497       ENDDO
498       IF ( bad_llcorner /= 0)  THEN
499          WRITE( message_string, *)  'at least one dimension of lower ',                           &
500                                     'left corner of one domain is not 0. ',                       &
501                                     'All lower left corners were set to (0, 0)'
502          CALL message( 'read_coupling_layout', 'PA0427', 0, 0, 0, 6, 0 )
503       ENDIF
504    ENDIF
505
506    CALL location_message( 'initialize communicators for nesting', 'finished' )
507
508 END SUBROUTINE read_coupling_layout
509
510#endif
511 END MODULE pmc_handle_communicator
Note: See TracBrowser for help on using the repository browser.