Changeset 1925 for palm


Ignore:
Timestamp:
Jun 7, 2016 11:34:42 AM (8 years ago)
Author:
hellstea
Message:

Error check for overlapping parallel nests added

Location:
palm/trunk/SOURCE
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/pmc_handle_communicator_mod.f90

    r1901 r1925  
    446446    TYPE(pmc_layout), DIMENSION(pmc_max_models) ::  domain_layouts
    447447
    448 !-- TO_DO: include anterp_relax_length_? into nestpar and communicate them.
    449448    NAMELIST /nestpar/  domain_layouts, nesting_datatransfer_mode, nesting_mode
    450449
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r1901 r1925  
    539539    INTEGER(iwp) ::  k                !:
    540540    INTEGER(iwp) ::  m                !:
     541    INTEGER(iwp) ::  mm               !:
     542    INTEGER(iwp) ::  nest_overlap     !:
    541543    INTEGER(iwp) ::  nomatch          !:
    542544    INTEGER(iwp) ::  nx_cl            !:
     
    546548    INTEGER(iwp), DIMENSION(5) ::  val    !:
    547549
     550
     551    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_xl   !:
     552    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_xr   !:   
     553    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_ys   !:
     554    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ch_yn   !:
    548555    REAL(wp) ::  dx_cl            !:
    549556    REAL(wp) ::  dy_cl            !:
     
    562569
    563570!
    564 !-- Get coordinates from all clients
     571!-- Corners of all children of the present parent
     572    IF ( ( SIZE( pmc_server_for_client ) - 1 > 0 ) .AND. myid == 0 )  THEN
     573       ALLOCATE( ch_xl(1:SIZE( pmc_server_for_client ) - 1) )
     574       ALLOCATE( ch_xr(1:SIZE( pmc_server_for_client ) - 1) )
     575       ALLOCATE( ch_ys(1:SIZE( pmc_server_for_client ) - 1) )
     576       ALLOCATE( ch_yn(1:SIZE( pmc_server_for_client ) - 1) )
     577    ENDIF
     578
     579!
     580!-- Get coordinates from all children
    565581    DO  m = 1, SIZE( pmc_server_for_client ) - 1
    566582
     
    589605
    590606!   
    591 !--       Get absolute coordinates from the client
     607!--       Get absolute coordinates from the child
    592608          ALLOCATE( cl_coord_x(-nbgp:nx_cl+nbgp) )
    593609          ALLOCATE( cl_coord_y(-nbgp:ny_cl+nbgp) )
     
    624640          ENDIF
    625641
     642!
     643!--       Check that parallel nest domains, if any, do not overlap.
     644          nest_overlap = 0
     645          IF ( SIZE( pmc_server_for_client ) - 1 > 0 )  THEN
     646             ch_xl(m) = cl_coord_x(-nbgp)
     647             ch_xr(m) = cl_coord_x(nx_cl+nbgp)
     648             ch_ys(m) = cl_coord_y(-nbgp)
     649             ch_yn(m) = cl_coord_y(ny_cl+nbgp)
     650
     651             IF ( m > 1 )  THEN
     652                DO mm = 1, m-1
     653                   IF ( ( ch_xl(m) < ch_xr(mm) .OR. ch_xr(m) > ch_xl(mm) ) .AND.  &
     654                        ( ch_ys(m) < ch_yn(mm) .OR. ch_yn(m) > ch_ys(mm) ) )  THEN                       
     655                      nest_overlap = 1
     656                   ENDIF
     657                ENDDO
     658             ENDIF
     659          ENDIF
     660
    626661          DEALLOCATE( cl_coord_x )
    627662          DEALLOCATE( cl_coord_y )
    628663
    629664!
    630 !--       Send coarse grid information to client
     665!--       Send coarse grid information to child
    631666          CALL pmc_send_to_client( client_id, define_coarse_grid_real,         &
    632667                                   SIZE( define_coarse_grid_real ), 0, 21,     &
     
    636671
    637672!
    638 !--       Send local grid to client
     673!--       Send local grid to child
    639674          CALL pmc_send_to_client( client_id, coord_x, nx+1+2*nbgp, 0, 24,     &
    640675                                   ierr )
     
    653688       CALL MPI_BCAST( nomatch, 1, MPI_INTEGER, 0, comm2d, ierr )
    654689       IF ( nomatch /= 0 ) THEN
    655           WRITE ( message_string, * )  'Error: nested client domain does ',    &
    656                                        'not fit into its server domain'
    657           CALL message( 'pmc_palm_setup_server', 'PA0XYZ', 1, 2, 0, 6, 0 )
     690          WRITE ( message_string, * )  'Error: nested child domain does ',    &
     691                                       'not fit into its parent domain'
     692          CALL message( 'pmc_palm_setup_server', 'PA0425', 3, 2, 0, 6, 0 )
     693       ENDIF
     694 
     695       CALL MPI_BCAST( nest_overlap, 1, MPI_INTEGER, 0, comm2d, ierr )
     696       IF ( nest_overlap /= 0 ) THEN
     697          WRITE ( message_string, * )  'Nested parallel child ',    &
     698                                       'domains overlap'
     699          CALL message( 'pmc_palm_setup_server', 'PA0426', 3, 2, 0, 6, 0 )
    658700       ENDIF
    659701     
     
    674716       CALL pmc_s_setind_and_allocmem( client_id )
    675717    ENDDO
     718
     719    IF ( ( SIZE( pmc_server_for_client ) - 1 > 0 ) .AND. myid == 0 )  THEN
     720       DEALLOCATE( ch_xl )
     721       DEALLOCATE( ch_xr )
     722       DEALLOCATE( ch_ys )
     723       DEALLOCATE( ch_yn )
     724    ENDIF
    676725
    677726 CONTAINS
     
    30883137    ELSE
    30893138
    3090        IF( nesting_datatransfer_mode == 'cascade' )  THEN
     3139       IF ( nesting_datatransfer_mode == 'cascade' )  THEN
    30913140
    30923141          CALL pmci_client_datatrans( server_to_client )
     
    30963145          CALL pmci_client_datatrans( client_to_server )
    30973146
    3098        ELSEIF( nesting_datatransfer_mode == 'overlap')  THEN
     3147       ELSEIF ( nesting_datatransfer_mode == 'overlap' )  THEN
    30993148
    31003149          CALL pmci_server_datatrans( server_to_client )
     
    31043153          CALL pmci_server_datatrans( client_to_server )
    31053154
    3106        ELSEIF( TRIM( nesting_datatransfer_mode ) == 'mixed' )  THEN
     3155       ELSEIF ( TRIM( nesting_datatransfer_mode ) == 'mixed' )  THEN
    31073156
    31083157          CALL pmci_server_datatrans( server_to_client )
     
    39173966      REAL(wp), DIMENSION(nzb:nzt+1), INTENT(IN)    ::  r2z   !:
    39183967     
    3919       INTEGER(iwp), DIMENSION(nxlg:nxrg), INTENT(IN) ::  ic    !:
    3920       INTEGER(iwp), DIMENSION(nysg:nyng), INTENT(IN) ::  jc    !:
    3921       INTEGER(iwp), DIMENSION(nzb:nzt+1), INTENT(IN) ::  kc    !:
     3968      INTEGER(iwp), DIMENSION(nxlg:nxrg), INTENT(IN) ::  ic   !:
     3969      INTEGER(iwp), DIMENSION(nysg:nyng), INTENT(IN) ::  jc   !:
     3970      INTEGER(iwp), DIMENSION(nzb:nzt+1), INTENT(IN) ::  kc   !:
    39223971     
    39233972      CHARACTER(LEN=1), INTENT(IN) :: var   !:
  • palm/trunk/SOURCE/time_integration.f90

    r1919 r1925  
    736736                CALL exchange_horiz( v, nbgp )
    737737                CALL exchange_horiz( w, nbgp )
    738                 CALL exchange_horiz( pt, nbgp )
     738                IF ( .NOT. neutral )  THEN
     739                   CALL exchange_horiz( pt, nbgp )
     740                ENDIF
    739741                IF ( humidity  .OR.  passive_scalar )  THEN
    740742                   CALL exchange_horiz( q, nbgp )
     
    11431145       dt_3d_old = dt_3d
    11441146       CALL timestep
     1147
     1148!
     1149!--    Synchronize the timestep in case of nested run.
     1150       IF ( nested_run )  THEN
     1151!
     1152!--       Synchronize by unifying the time step.
     1153!--       Global minimum of all time-steps is used for all.
     1154          CALL pmci_synchronize
     1155       ENDIF
    11451156
    11461157!
     
    11711182
    11721183!
    1173 !--    Synchronize the timestep in case of nested run.
    1174        IF ( nested_run )  THEN
    1175 !
    1176 !--       Synchronize by unifying the time step.
    1177 !--       Global minimum of all time-steps is used for all.
    1178           CALL pmci_synchronize
    1179        ENDIF
    1180 
    1181 !
    11821184!--    Output elapsed simulated time in form of a progress bar on stdout
    11831185       IF ( myid == 0 )  CALL output_progress_bar
Note: See TracChangeset for help on using the changeset viewer.