Ignore:
Timestamp:
Dec 14, 2017 5:12:51 PM (7 years ago)
Author:
kanani
Message:

Merge of branch palm4u into trunk

Location:
palm/trunk
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk

  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/init_pegrid.f90

    r2600 r2696  
    11!> @file init_pegrid.f90
    22!------------------------------------------------------------------------------!
    3 ! This file is part of PALM.
     3! This file is part of the PALM model system.
    44!
    55! PALM is free software: you can redistribute it and/or modify it under the
     
    2525! -----------------
    2626! $Id$
     27! 3D-Integer exchange on multigrid level (MS)
     28! Forcing implemented (MS)
     29!
     30! 2600 2017-11-01 14:11:20Z raasch
    2731! calculation of block-I/O quantitites removed (is now done in parin)
    2832!
     
    204208!> user)and computation of the grid point number and array bounds of the local
    205209!> domains.
     210!> @todo: remove MPI-data types for 2D exchange on coarse multigrid level (not
     211!>        used any more)
    206212!------------------------------------------------------------------------------!
    207213 SUBROUTINE init_pegrid
     
    210216    USE control_parameters,                                                    &
    211217        ONLY:  bc_lr, bc_ns, coupling_mode, coupling_mode_remote,              &
    212                coupling_topology, gathered_size, grid_level,                   &
     218               coupling_topology, force_bound_l, force_bound_n, force_bound_r, &
     219               force_bound_s, gathered_size, grid_level,                       &
    213220               grid_level_count, inflow_l, inflow_n, inflow_r, inflow_s,       &
    214221               maximum_grid_level, message_string,                             &
     
    352359    CALL MPI_CART_SHIFT( comm2d, 0, 1, pleft, pright, ierr )
    353360    CALL MPI_CART_SHIFT( comm2d, 1, 1, psouth, pnorth, ierr )
    354 
    355361!
    356362!-- In case of cyclic boundary conditions, a y-shift at the boundaries in
     
    405411       ENDIF
    406412    ENDIF
    407 
    408413!
    409414!-- Vertical nesting: store four lists that identify partner ranks to exchange
     
    700705#endif
    701706
    702 
    703707!
    704708!-- Determine the number of ghost point layers
     
    823827!-- Create custom MPI vector datatypes for contiguous data transfer
    824828    IF ( vnested )  CALL vnest_init_pegrid_domain
    825 
    826829
    827830#else
     
    10961099!-- Do these calculations for the model grid and (if necessary) also
    10971100!-- for the coarser grid levels used in the multigrid method
    1098     ALLOCATE ( ngp_xz(0:maximum_grid_level), ngp_yz(0:maximum_grid_level),     &
    1099                type_xz(0:maximum_grid_level), type_yz(0:maximum_grid_level) )
     1101    ALLOCATE ( ngp_xz(0:maximum_grid_level),                                   &
     1102               ngp_xz_int(0:maximum_grid_level),                               &
     1103               ngp_yz(0:maximum_grid_level),                                   &
     1104               ngp_yz_int(0:maximum_grid_level),                               &
     1105               type_xz(0:maximum_grid_level),                                  &
     1106               type_xz_int(0:maximum_grid_level),                              &
     1107               type_yz(0:maximum_grid_level),                                  &
     1108               type_yz_int(0:maximum_grid_level) )
    11001109
    11011110    nxl_l = nxl; nxr_l = nxr; nys_l = nys; nyn_l = nyn; nzb_l = nzb; nzt_l = nzt
     
    11251134
    11261135!
     1136!-- Define data types for exchange of 3D Integer arrays.
     1137    ngp_yz_int(0) = (nzt - nzb + 2) * (nyn - nys + 1 + 2 * nbgp)
     1138
     1139    CALL MPI_TYPE_VECTOR( nxr-nxl+1+2*nbgp, nbgp*(nzt-nzb+2), ngp_yz_int(0),   &
     1140                          MPI_INTEGER, type_xz_int(0), ierr )
     1141    CALL MPI_TYPE_COMMIT( type_xz_int(0), ierr )
     1142
     1143    CALL MPI_TYPE_VECTOR( nbgp, ngp_yz_int(0), ngp_yz_int(0), MPI_INTEGER,     &
     1144                          type_yz_int(0), ierr )
     1145    CALL MPI_TYPE_COMMIT( type_yz_int(0), ierr )
     1146
     1147!
    11271148!-- Definition of MPI-datatypes for multigrid method (coarser level grids)
    11281149    IF ( psolver(1:9) == 'multigrid' )  THEN
     
    11311152       DO  i = maximum_grid_level, 1 , -1
    11321153!
    1133 !--       For 3D-exchange
     1154!--       For 3D-exchange on different multigrid level, one ghost point for
     1155!--       REAL arrays, two ghost points for INTEGER arrays
    11341156          ngp_xz(i) = (nzt_l - nzb_l + 2) * (nxr_l - nxl_l + 3)
    11351157          ngp_yz(i) = (nzt_l - nzb_l + 2) * (nyn_l - nys_l + 3)
    11361158
    1137           CALL MPI_TYPE_VECTOR( nxr_l-nxl_l+3, nzt_l-nzb_l+2, ngp_yz(i), &
     1159          ngp_xz_int(i) = (nzt_l - nzb_l + 2) * (nxr_l - nxl_l + 3)
     1160          ngp_yz_int(i) = (nzt_l - nzb_l + 2) * (nyn_l - nys_l + 3)
     1161!
     1162!--       MPI data type for REAL arrays, for xz-layers
     1163          CALL MPI_TYPE_VECTOR( nxr_l-nxl_l+3, nzt_l-nzb_l+2, ngp_yz(i),       &
    11381164                                MPI_REAL, type_xz(i), ierr )
    11391165          CALL MPI_TYPE_COMMIT( type_xz(i), ierr )
    11401166
     1167!
     1168!--       MPI data type for INTEGER arrays, for xz-layers
     1169          CALL MPI_TYPE_VECTOR( nxr_l-nxl_l+3, nzt_l-nzb_l+2, ngp_yz_int(i),   &
     1170                                MPI_INTEGER, type_xz_int(i), ierr )
     1171          CALL MPI_TYPE_COMMIT( type_xz_int(i), ierr )
     1172
     1173!
     1174!--       MPI data type for REAL arrays, for yz-layers
    11411175          CALL MPI_TYPE_VECTOR( 1, ngp_yz(i), ngp_yz(i), MPI_REAL, type_yz(i), &
    11421176                                ierr )
    11431177          CALL MPI_TYPE_COMMIT( type_yz(i), ierr )
     1178!
     1179!--       MPI data type for INTEGER arrays, for yz-layers
     1180          CALL MPI_TYPE_VECTOR( 1, ngp_yz_int(i), ngp_yz_int(i), MPI_INTEGER,  &
     1181                                type_yz_int(i), ierr )
     1182          CALL MPI_TYPE_COMMIT( type_yz_int(i), ierr )
    11441183
    11451184
     
    11551194          CALL MPI_TYPE_COMMIT( type_y_int(i), ierr )
    11561195
    1157 
    1158 
    11591196          nxl_l = nxl_l / 2
    11601197          nxr_l = nxr_l / 2
     
    11661203
    11671204    ENDIF
    1168 !
    1169 !-- Define data types for exchange of 3D Integer arrays.
    1170     ngp_yz_int = (nzt - nzb + 2) * (nyn - nys + 1 + 2 * nbgp)
    1171 
    1172     CALL MPI_TYPE_VECTOR( nxr-nxl+1+2*nbgp, nbgp*(nzt-nzb+2), ngp_yz_int, &
    1173                           MPI_INTEGER, type_xz_int, ierr )
    1174     CALL MPI_TYPE_COMMIT( type_xz_int, ierr )
    1175 
    1176     CALL MPI_TYPE_VECTOR( nbgp, ngp_yz_int, ngp_yz_int, MPI_INTEGER, type_yz_int, &
    1177                           ierr )
    1178     CALL MPI_TYPE_COMMIT( type_yz_int, ierr )
    11791205
    11801206#endif
     
    11901216       ELSEIF ( bc_lr == 'nested' )  THEN
    11911217          nest_bound_l = .TRUE.
     1218       ELSEIF ( bc_lr == 'forcing' )  THEN
     1219          force_bound_l = .TRUE.
    11921220       ENDIF
    11931221    ENDIF
     
    12001228       ELSEIF ( bc_lr == 'nested' )  THEN
    12011229          nest_bound_r = .TRUE.
     1230       ELSEIF ( bc_lr == 'forcing' )  THEN
     1231          force_bound_r = .TRUE.
    12021232       ENDIF
    12031233    ENDIF
     
    12101240       ELSEIF ( bc_ns == 'nested' )  THEN
    12111241          nest_bound_s = .TRUE.
     1242       ELSEIF ( bc_ns == 'forcing' )  THEN
     1243          force_bound_s = .TRUE.
    12121244       ENDIF
    12131245    ENDIF
     
    12201252       ELSEIF ( bc_ns == 'nested' )  THEN
    12211253          nest_bound_n = .TRUE.
     1254       ELSEIF ( bc_ns == 'forcing' )  THEN
     1255          force_bound_n = .TRUE.
    12221256       ENDIF
    12231257    ENDIF
     
    12951329!-- At the inflow or outflow, u or v, respectively, have to be calculated for
    12961330!-- one more grid point.
    1297     IF ( inflow_l .OR. outflow_l .OR. nest_bound_l )  THEN
     1331    IF ( inflow_l .OR. outflow_l .OR. nest_bound_l .OR. force_bound_l )  THEN
    12981332       nxlu = nxl + 1
    12991333    ELSE
    13001334       nxlu = nxl
    13011335    ENDIF
    1302     IF ( inflow_s .OR. outflow_s .OR. nest_bound_s )  THEN
     1336    IF ( inflow_s .OR. outflow_s .OR. nest_bound_s .OR. force_bound_s )  THEN
    13031337       nysv = nys + 1
    13041338    ELSE
Note: See TracChangeset for help on using the changeset viewer.