Ignore:
Timestamp:
Nov 20, 2018 5:04:13 PM (5 years ago)
Author:
suehring
Message:

Revise ghost point exchange in netcdf-data input; new routine for ghost point exchange of 1-Byte Integer; Remove tabs in chemistry model which prevent compilation with gfortran and debug options

File:
1 edited

Legend:

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

    r3183 r3542  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! - New routine for exchange of 8-bit integer arrays
     23! - Set Neumann conditions also at radiation boundary
    2324!
    2425! Former revisions:
     
    213214
    214215
    215 
    216216!------------------------------------------------------------------------------!
    217217! Description:
    218218! ------------
    219219!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
    220 !> boundary conditions, respectively, for 2D integer arrays.
    221 !------------------------------------------------------------------------------!
    222  
    223  SUBROUTINE exchange_horiz_2d_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nbgp_local )
     220!> boundary conditions, respectively, for 2D 8-bit integer arrays.
     221!------------------------------------------------------------------------------!
     222 SUBROUTINE exchange_horiz_2d_byte( ar, nys_l, nyn_l, nxl_l, nxr_l, nbgp_local )
    224223
    225224
    226225    USE control_parameters,                                                    &
    227226        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,                 &
    228                bc_dirichlet_s, bc_lr_cyc, bc_ns_cyc, bc_radiation_l,           &
     227               bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
     228               bc_radiation_s, bc_lr_cyc, bc_ns_cyc, bc_radiation_l,           &
    229229               bc_radiation_n, bc_radiation_r, bc_radiation_s, grid_level
    230230       
     
    245245    INTEGER(iwp) ::  nbgp_local  !< number of ghost layers to be exchanged
    246246
     247    INTEGER(KIND=1), DIMENSION(nys_l-nbgp_local:nyn_l+nbgp_local,              &
     248                               nxl_l-nbgp_local:nxr_l+nbgp_local) ::  ar  !< treated array
     249
     250    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'start' )
     251
     252#if defined( __parallel )
     253
     254!
     255!-- Exchange of lateral boundary values for parallel computers
     256    IF ( pdims(1) == 1 )  THEN
     257
     258!
     259!--    One-dimensional decomposition along y, boundary values can be exchanged
     260!--    within the PE memory
     261       ar(:,nxl_l-nbgp_local:nxl_l-1) = ar(:,nxr_l-nbgp_local+1:nxr_l)
     262       ar(:,nxr_l+1:nxr_l+nbgp_local) = ar(:,nxl_l:nxl_l+nbgp_local-1)
     263
     264    ELSE
     265!
     266!--    Send left boundary, receive right one
     267       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxl_l),   1,                     &
     268                          type_y_byte, pleft,  0,                              &
     269                          ar(nys_l-nbgp_local,nxr_l+1), 1,                     &
     270                          type_y_byte, pright, 0,                              &
     271                          comm2d, status, ierr )
     272!
     273!--    Send right boundary, receive left one
     274       CALL MPI_SENDRECV( ar(nys_l-nbgp_local,nxr_l+1-nbgp_local), 1,          &
     275                          type_y_byte, pright, 1,                              &
     276                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,          &
     277                          type_y_byte, pleft,  1,                              &
     278                          comm2d, status, ierr )                         
     279
     280    ENDIF
     281
     282    IF ( pdims(2) == 1 )  THEN
     283!
     284!--    One-dimensional decomposition along x, boundary values can be exchanged
     285!--    within the PE memory
     286       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
     287       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
     288
     289
     290    ELSE
     291!
     292!--    Send front boundary, receive rear one
     293       CALL MPI_SENDRECV( ar(nys_l,nxl_l-nbgp_local),   1,                    &
     294                          type_x_byte, psouth, 0,                             &
     295                          ar(nyn_l+1,nxl_l-nbgp_local), 1,                    &
     296                          type_x_byte, pnorth, 0,                             &
     297                          comm2d, status, ierr )                         
     298
     299!
     300!--    Send rear boundary, receive front one
     301       CALL MPI_SENDRECV( ar(nyn_l+1-nbgp_local,nxl_l-nbgp_local), 1,         &
     302                          type_x_byte, pnorth, 1,                             &
     303                          ar(nys_l-nbgp_local,nxl_l-nbgp_local),   1,         &
     304                          type_x_byte, psouth, 1,                             &
     305                          comm2d, status, ierr )
     306
     307    ENDIF
     308
     309#else
     310
     311!
     312!-- Lateral boundary conditions in the non-parallel case
     313    IF ( bc_lr_cyc )  THEN
     314       ar(:,nxl_l-nbgp_local:nxl_l-1) = ar(:,nxr_l-nbgp_local+1:nxr_l)
     315       ar(:,nxr_l+1:nxr_l+nbgp_local) = ar(:,nxl_l:nxl_l+nbgp_local-1)
     316    ENDIF
     317
     318    IF ( bc_ns_cyc )  THEN
     319       ar(nys_l-nbgp_local:nys_l-1,:) = ar(nyn_l+1-nbgp_local:nyn_l,:)
     320       ar(nyn_l+1:nyn_l+nbgp_local,:) = ar(nys_l:nys_l-1+nbgp_local,:)
     321    ENDIF
     322
     323#endif
     324!
     325!-- Neumann-conditions at inflow/outflow/nested boundaries
     326    IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
     327       DO  i = nbgp_local, 1, -1
     328         ar(:,nxl_l-i) = ar(:,nxl_l)
     329       ENDDO
     330    ENDIF
     331    IF ( bc_dirichlet_r  .OR.  bc_radiation_r  )  THEN
     332       DO  i = 1, nbgp_local
     333          ar(:,nxr_l+i) = ar(:,nxr_l)
     334       ENDDO
     335    ENDIF
     336    IF ( bc_dirichlet_s  .OR.  bc_radiation_s  )  THEN
     337       DO  i = nbgp_local, 1, -1
     338         ar(nys_l-i,:) = ar(nys_l,:)
     339       ENDDO
     340    ENDIF
     341    IF ( bc_dirichlet_n  .OR.  bc_radiation_n  )  THEN
     342       DO  i = 1, nbgp_local
     343         ar(nyn_l+i,:) = ar(nyn_l,:)
     344       ENDDO
     345    ENDIF
     346
     347    CALL cpu_log( log_point_s(13), 'exchange_horiz_2d', 'stop' )
     348
     349 END SUBROUTINE exchange_horiz_2d_byte
     350 
     351
     352!------------------------------------------------------------------------------!
     353! Description:
     354! ------------
     355!> Exchange of lateral (ghost) boundaries (parallel computers) and cyclic
     356!> boundary conditions, respectively, for 2D 32-bit integer arrays.
     357!------------------------------------------------------------------------------!
     358 SUBROUTINE exchange_horiz_2d_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nbgp_local )
     359
     360
     361    USE control_parameters,                                                    &
     362        ONLY:  bc_dirichlet_l, bc_dirichlet_n, bc_dirichlet_r,                 &
     363               bc_dirichlet_s, bc_radiation_l, bc_radiation_n, bc_radiation_r, &
     364               bc_radiation_s, bc_lr_cyc, bc_ns_cyc, bc_radiation_l,           &
     365               bc_radiation_n, bc_radiation_r, bc_radiation_s, grid_level
     366       
     367    USE cpulog,                                                                &
     368        ONLY:  cpu_log, log_point_s
     369               
     370    USE kinds
     371   
     372    USE pegrid
     373
     374    IMPLICIT NONE
     375
     376    INTEGER(iwp) ::  i           !< dummy index to zero-gradient conditions at in/outflow boundaries
     377    INTEGER(iwp) ::  nxl_l       !< local index bound at current grid level, left side
     378    INTEGER(iwp) ::  nxr_l       !< local index bound at current grid level, right side
     379    INTEGER(iwp) ::  nyn_l       !< local index bound at current grid level, north side
     380    INTEGER(iwp) ::  nys_l       !< local index bound at current grid level, south side
     381    INTEGER(iwp) ::  nbgp_local  !< number of ghost layers to be exchanged
     382
    247383    INTEGER(iwp), DIMENSION(nys_l-nbgp_local:nyn_l+nbgp_local,                 &
    248384                            nxl_l-nbgp_local:nxr_l+nbgp_local) ::  ar  !< treated array
     
    324460!
    325461!-- Neumann-conditions at inflow/outflow/nested boundaries
    326     IF ( bc_dirichlet_l )  THEN
     462    IF ( bc_dirichlet_l  .OR.  bc_radiation_l )  THEN
    327463       DO  i = nbgp_local, 1, -1
    328464         ar(:,nxl_l-i) = ar(:,nxl_l)
    329465       ENDDO
    330466    ENDIF
    331     IF ( bc_dirichlet_r )  THEN
     467    IF ( bc_dirichlet_r  .OR.  bc_radiation_r  )  THEN
    332468       DO  i = 1, nbgp_local
    333469          ar(:,nxr_l+i) = ar(:,nxr_l)
    334470       ENDDO
    335471    ENDIF
    336     IF ( bc_dirichlet_s )  THEN
     472    IF ( bc_dirichlet_s  .OR.  bc_radiation_s  )  THEN
    337473       DO  i = nbgp_local, 1, -1
    338474         ar(nys_l-i,:) = ar(nys_l,:)
    339475       ENDDO
    340476    ENDIF
    341     IF ( bc_dirichlet_n )  THEN
     477    IF ( bc_dirichlet_n  .OR.  bc_radiation_n  )  THEN
    342478       DO  i = 1, nbgp_local
    343479         ar(nyn_l+i,:) = ar(nyn_l,:)
Note: See TracChangeset for help on using the changeset viewer.