Ignore:
Timestamp:
Feb 23, 2021 4:32:41 PM (3 years ago)
Author:
hellstea
Message:

user switch for particle coupling added

File:
1 edited

Legend:

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

    r4828 r4883  
    2525! -----------------
    2626! $Id$
     27! User switch for particle coupling added. Some code reformatting according to follow PALM coding standard.
     28! Some missing doxygen comments added.
     29!
     30! 4828 2021-01-05 11:21:41Z Giersch
    2731! Bugfix in setting up the nesting configuration for chemical and aerosol species in case of more
    2832! than one child domain
     
    456460
    457461    INTEGER(iwp), SAVE ::  comm_world_nesting  !< Global nesting communicator
    458     INTEGER(iwp), SAVE ::  cpl_id  = 1         !<
     462    INTEGER(iwp), SAVE ::  cpl_id  = 1         !< Model (domain) id (1 for root, 2,... for nested domains).
    459463    INTEGER(iwp), SAVE ::  cpl_npe_total       !<
    460464    INTEGER(iwp), SAVE ::  cpl_parent_id       !<
     
    470474
    471475    LOGICAL, SAVE ::  nested_run = .FALSE.        !< general switch
     476    LOGICAL, SAVE ::  particle_coupling = .TRUE.  !< switch for particle coupling (meaningful only when lpm is used)
    472477    LOGICAL, SAVE ::  rans_mode_parent = .FALSE.  !< mode of parent model (.F. - LES mode, .T. - RANS mode)
    473478!
     
    561566!
    562567!-- Work arrays for interpolation and user-defined type definitions for horizontal work-array exchange
    563     INTEGER(iwp) ::  workarr_lr_exchange_type   !<
    564     INTEGER(iwp) ::  workarr_sn_exchange_type   !<
    565     INTEGER(iwp) ::  workarr_t_exchange_type_x  !<
    566     INTEGER(iwp) ::  workarr_t_exchange_type_y  !<
     568    INTEGER(iwp) ::  workarr_lr_exchange_type   !< type definition for work-array exchange on left and right boundaries
     569    INTEGER(iwp) ::  workarr_sn_exchange_type   !< type definition for work-array exchange on south and north boundaries
     570    INTEGER(iwp) ::  workarr_t_exchange_type_x  !< type definition for work-array exchange on top boundary between left-right
     571                                                !< neighbouring subdomains
     572    INTEGER(iwp) ::  workarr_t_exchange_type_y  !< type definition for work-array exchange on top boundary between south-north
     573                                                !< neighbouring subdomains
    567574
    568575    INTEGER(iwp), DIMENSION(3) ::  parent_grid_info_int  !< Array for communicating the parent-grid dimensions to its children.
     
    572579                                                      !< children.
    573580
    574     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_lr  !<
    575     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_sn  !<
    576     REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_t   !<
     581    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_lr  !< work array for interpolation on left and right boundaries
     582    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_sn  !< work array for interpolation on south and north boundaries
     583    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  workarr_t   !< work array for interpolation on top boundary
    577584
    578585    TYPE parentgrid_def
     
    599606!-- Variables for particle coupling
    600607    TYPE, PUBLIC :: childgrid_def
    601        INTEGER(iwp) ::  nx  !<
    602        INTEGER(iwp) ::  ny  !<
    603        INTEGER(iwp) ::  nz  !<
    604        REAL(wp)     ::  dx  !<
    605        REAL(wp)     ::  dy  !<
    606        REAL(wp)     ::  dz  !<
    607        REAL(wp)     ::  lx_coord, lx_coord_b !<   ! split onto separate lines
    608        REAL(wp)     ::  rx_coord, rx_coord_b !<
    609        REAL(wp)     ::  sy_coord, sy_coord_b !<
    610        REAL(wp)     ::  ny_coord, ny_coord_b !<
    611        REAL(wp)     ::  uz_coord, uz_coord_b !<
     608       INTEGER(iwp) ::  nx          !<
     609       INTEGER(iwp) ::  ny          !<
     610       INTEGER(iwp) ::  nz          !<
     611       REAL(wp)     ::  dx          !<
     612       REAL(wp)     ::  dy          !<
     613       REAL(wp)     ::  dz          !<
     614       REAL(wp)     ::  lx_coord    !<
     615       REAL(wp)     ::  rx_coord    !<
     616       REAL(wp)     ::  sy_coord    !<
     617       REAL(wp)     ::  ny_coord    !<
     618       REAL(wp)     ::  uz_coord    !<
     619       REAL(wp)     ::  lx_coord_b  !<
     620       REAL(wp)     ::  rx_coord_b  !<
     621       REAL(wp)     ::  sy_coord_b  !<
     622       REAL(wp)     ::  ny_coord_b  !<
     623       REAL(wp)     ::  uz_coord_b  !<       
    612624    END TYPE childgrid_def
    613625
     
    685697           nesting_mode,                                                                           &
    686698           parent_to_child,                                                                        &
     699           particle_coupling,                                                                      &
    687700           rans_mode_parent
    688701
     
    711724    IMPLICIT NONE
    712725
    713     INTEGER(iwp), INTENT(OUT) ::  world_comm  !<
     726    INTEGER(iwp), INTENT(OUT) ::  world_comm  !< global communicator
    714727
    715728#if defined( __parallel )
    716729
    717     INTEGER(iwp) ::  pmc_status  !<
     730    INTEGER(iwp) ::  pmc_status  !< status parameter indicating if the nesting_parameters namelist
     731                                 !< was succesfully input or not 
    718732
    719733
    720734    CALL pmc_init_model( world_comm, nesting_datatransfer_mode, nesting_mode,                      &
    721                          anterpolation_buffer_width, anterpolation_starting_height, pmc_status )
    722 
     735                         anterpolation_buffer_width, anterpolation_starting_height,                &
     736                         particle_coupling, pmc_status )
    723737    IF ( pmc_status == pmc_no_namelist_found )  THEN
    724738!
     
    17451759    IMPLICIT NONE
    17461760
    1747     INTEGER(iwp) ::  i       !< Child-grid index in the x-direction
    1748     INTEGER(iwp) ::  ii      !< Parent-grid index in the x-direction
    1749     INTEGER(iwp) ::  istart  !<
    1750     INTEGER(iwp) ::  ir      !<
    1751     INTEGER(iwp) ::  iw      !< Child-grid index limited to -1 <= iw <= nx+1 for wall_flags_total_0
    1752     INTEGER(iwp) ::  j       !< Child-grid index in the y-direction
    1753     INTEGER(iwp) ::  jj      !< Parent-grid index in the y-direction
    1754     INTEGER(iwp) ::  jstart  !<
    1755     INTEGER(iwp) ::  jr      !<
    1756     INTEGER(iwp) ::  jw      !< Child-grid index limited to -1 <= jw <= ny+1 for wall_flags_total_0
    1757     INTEGER(iwp) ::  k       !< Child-grid index in the z-direction
    1758     INTEGER(iwp) ::  kk      !< Parent-grid index in the z-direction
    1759     INTEGER(iwp) ::  kstart  !<
    1760     INTEGER(iwp) ::  kw      !< Child-grid index limited to kw <= nzt+1 for wall_flags_total_0
    1761 
    1762     REAL(wp) ::  tolex  !< Tolerance for grid-line matching in x-direction
    1763     REAL(wp) ::  toley  !< Tolerance for grid-line matching in y-direction
    1764     REAL(wp) ::  tolez  !< Tolerance for grid-line matching in z-direction
     1761    INTEGER(iwp) ::  i       !< child-grid index in the x-direction
     1762    INTEGER(iwp) ::  ii      !< parent-grid index in the x-direction
     1763    INTEGER(iwp) ::  istart  !< starting index for the index-mapping search loop in the x-direction
     1764    INTEGER(iwp) ::  ir      !< search-loop running index in the x-direction
     1765    INTEGER(iwp) ::  iw      !< child-grid index limited to -1 <= iw <= nx+1 for wall_flags_total_0
     1766    INTEGER(iwp) ::  j       !< child-grid index in the y-direction
     1767    INTEGER(iwp) ::  jj      !< parent-grid index in the y-direction
     1768    INTEGER(iwp) ::  jstart  !< starting index for the index-mapping search loop in the y-direction
     1769    INTEGER(iwp) ::  jr      !< search-loop running index in the y-direction
     1770    INTEGER(iwp) ::  jw      !< child-grid index limited to -1 <= jw <= ny+1 for wall_flags_total_0
     1771    INTEGER(iwp) ::  k       !< child-grid index in the z-direction
     1772    INTEGER(iwp) ::  kk      !< parent-grid index in the z-direction
     1773    INTEGER(iwp) ::  kstart  !< starting index for the index-mapping search loop in the z-direction
     1774    INTEGER(iwp) ::  kw      !< child-grid index limited to kw <= nzt+1 for wall_flags_total_0
     1775
     1776    REAL(wp) ::  tolex  !< tolerance for grid-line matching in x-direction
     1777    REAL(wp) ::  toley  !< tolerance for grid-line matching in y-direction
     1778    REAL(wp) ::  tolez  !< tolerance for grid-line matching in z-direction
    17651779
    17661780!
     
    26382652    IMPLICIT NONE
    26392653
    2640     INTEGER(iwp) ::  i  !<
    2641     INTEGER(iwp) ::  j  !<
     2654    INTEGER(iwp) ::  i  !< grid index in the x-direction
     2655    INTEGER(iwp) ::  j  !< grid index in the y-direction
    26422656
    26432657!
     
    37133727    IMPLICIT NONE
    37143728
    3715     INTEGER(iwp), INTENT(IN) ::  direction  !< Transfer direction: parent_to_child or child_to_parent
     3729    INTEGER(iwp), INTENT(IN) ::  direction  !< transfer direction: parent_to_child or child_to_parent
    37163730
    37173731#if defined( __parallel )
    37183732
    3719     REAL(wp), DIMENSION(1) ::  dtl  !< Time step size
     3733    REAL(wp), DIMENSION(1) ::  dtl  !< time step size
    37203734
    37213735
     
    41264140 
    41274141    IMPLICIT NONE
    4128     INTEGER(iwp) ::  lb  !< Running index for aerosol size bins
    4129     INTEGER(iwp) ::  lc  !< Running index for aerosol mass bins
    4130     INTEGER(iwp) ::  lg  !< Running index for salsa gases
    4131     INTEGER(iwp) ::  n   !< Running index for number of chemical species
     4142    INTEGER(iwp) ::  lb  !< running index for aerosol size bins
     4143    INTEGER(iwp) ::  lc  !< running index for aerosol mass bins
     4144    INTEGER(iwp) ::  lg  !< running index for salsa gases
     4145    INTEGER(iwp) ::  n   !< running index for number of chemical species
    41324146
    41334147
     
    42164230    IMPLICIT NONE
    42174231
    4218     CHARACTER(LEN=1), INTENT(IN) ::  edge  !< Edge symbol: 'l' or 'r'
    4219     CHARACTER(LEN=1), INTENT(IN) ::  var   !< Variable symbol: 'u', 'v', 'w' or 's'
    4220 
    4221     INTEGER(iwp), INTENT(IN) ::  kct  !< The parent-grid index in z-direction just below the boundary value node
    4222 
    4223     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< Indicates start index of child cells belonging to certain
     4232    CHARACTER(LEN=1), INTENT(IN) ::  edge  !< edge symbol: 'l' or 'r'
     4233    CHARACTER(LEN=1), INTENT(IN) ::  var   !< variable symbol: 'u', 'v', 'w' or 's'
     4234
     4235    INTEGER(iwp), INTENT(IN) ::  kct  !< the parent-grid index in z-direction just below the boundary value node
     4236
     4237    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< indicates start index of child cells belonging to certain
    42244238                                                            !< parent cell - y direction
    4225     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< Indicates end index of child cells belonging to certain
     4239    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< indicates end index of child cells belonging to certain
    42264240                                                            !< parent cell - y direction
    4227     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< Indicates start index of child cells belonging to certain
     4241    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< indicates start index of child cells belonging to certain
    42284242                                                            !< parent cell - z direction
    4229     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< Indicates end index of child cells belonging to certain
     4243    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< indicates end index of child cells belonging to certain
    42304244                                                            !< parent cell - z direction
    42314245
     
    42364250!
    42374251!-- Local variables:
    4238     INTEGER(iwp) ::  icb    !< Fixed child-grid index in the x-direction pointing to the node just behind the
     4252    INTEGER(iwp) ::  icb    !< fixed child-grid index in the x-direction pointing to the node just behind the
    42394253                            !< boundary-value node
    4240     INTEGER(iwp) ::  icbc   !< Fixed child-grid index in the x-direction pointing to the boundary-value nodes
    4241     INTEGER(iwp) ::  icbgp  !< Index running over the redundant boundary ghost points in the x-direction
     4254    INTEGER(iwp) ::  icbc   !< fixed child-grid index in the x-direction pointing to the boundary-value nodes
     4255    INTEGER(iwp) ::  icbgp  !< index running over the redundant boundary ghost points in the x-direction
    42424256    INTEGER(iwp) ::  ierr   !< MPI error code
    4243     INTEGER(iwp) ::  ipbeg  !< Parent-grid index in the x-direction pointing to the starting point of workarr_lr
     4257    INTEGER(iwp) ::  ipbeg  !< parent-grid index in the x-direction pointing to the starting point of workarr_lr
    42444258                            !< in the parent-grid array
    4245     INTEGER(iwp) ::  ipw    !< Reduced parent-grid index in the x-direction for workarr_lr pointing to
     4259    INTEGER(iwp) ::  ipw    !< reduced parent-grid index in the x-direction for workarr_lr pointing to
    42464260                            !< the boundary ghost node
    4247     INTEGER(iwp) ::  ipwp   !< Reduced parent-grid index in the x-direction for workarr_lr pointing to
     4261    INTEGER(iwp) ::  ipwp   !< reduced parent-grid index in the x-direction for workarr_lr pointing to
    42484262                            !< the first prognostic node
    4249     INTEGER(iwp) ::  jc     !< Running child-grid index in the y-direction
    4250     INTEGER(iwp) ::  jp     !< Running parent-grid index in the y-direction
    4251     INTEGER(iwp) ::  kc     !< Running child-grid index in the z-direction
    4252     INTEGER(iwp) ::  kp     !< Running parent-grid index in the z-direction
    4253 
    4254     REAL(wp) ::  cb          !< Interpolation coefficient for the boundary ghost node
    4255     REAL(wp) ::  cp          !< Interpolation coefficient for the first prognostic node
    4256     REAL(wp) ::  c_interp_1  !< Value interpolated to the flux point in x direction from the parent-grid data
    4257     REAL(wp) ::  c_interp_2  !< Auxiliary value interpolated  to the flux point in x direction from the parent-grid data
     4263    INTEGER(iwp) ::  jc     !< running child-grid index in the y-direction
     4264    INTEGER(iwp) ::  jp     !< running parent-grid index in the y-direction
     4265    INTEGER(iwp) ::  kc     !< running child-grid index in the z-direction
     4266    INTEGER(iwp) ::  kp     !< running parent-grid index in the z-direction
     4267
     4268    REAL(wp) ::  cb          !< interpolation coefficient for the boundary ghost node
     4269    REAL(wp) ::  cp          !< interpolation coefficient for the first prognostic node
     4270    REAL(wp) ::  c_interp_1  !< value interpolated to the flux point in x direction from the parent-grid data
     4271    REAL(wp) ::  c_interp_2  !< auxiliary value interpolated  to the flux point in x direction from the parent-grid data
     4272   
    42584273!
    42594274!-- Check which edge is to be handled
     
    44534468    IMPLICIT NONE
    44544469
    4455     CHARACTER(LEN=1), INTENT(IN) ::  edge  !< Edge symbol: 's' or 'n'
    4456     CHARACTER(LEN=1), INTENT(IN) ::  var   !< Variable symbol: 'u', 'v', 'w' or 's'
    4457 
    4458     INTEGER(iwp), INTENT(IN) ::  kct  !< The parent-grid index in z-direction just below the boundary value node
    4459 
    4460     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< Indicates start index of child cells belonging to certain
     4470    CHARACTER(LEN=1), INTENT(IN) ::  edge  !< edge symbol: 's' or 'n'
     4471    CHARACTER(LEN=1), INTENT(IN) ::  var   !< variable symbol: 'u', 'v', 'w' or 's'
     4472
     4473    INTEGER(iwp), INTENT(IN) ::  kct  !< the parent-grid index in z-direction just below the boundary value node
     4474
     4475    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< indicates start index of child cells belonging to certain
    44614476                                                            !< parent cell - x direction
    4462     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< Indicates end index of child cells belonging to certain
     4477    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< indicates end index of child cells belonging to certain
    44634478                                                            !< parent cell - x direction
    4464     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< Indicates start index of child cells belonging to certain
     4479    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< indicates start index of child cells belonging to certain
    44654480                                                            !< parent cell - z direction
    4466     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< Indicates end index of child cells belonging to certain
     4481    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< indicates end index of child cells belonging to certain
    44674482                                                            !< parent cell - z direction
    44684483
     
    44724487!
    44734488!-- Local variables:
    4474     INTEGER(iwp) ::  ic     !< Running child-grid index in the x-direction
     4489    INTEGER(iwp) ::  ic     !< running child-grid index in the x-direction
    44754490    INTEGER(iwp) ::  ierr   !< MPI error code
    4476     INTEGER(iwp) ::  ip     !< Running parent-grid index in the x-direction
    4477     INTEGER(iwp) ::  jcb    !< Fixed child-grid index in the y-direction pointing to the node just behind the
     4491    INTEGER(iwp) ::  ip     !< running parent-grid index in the x-direction
     4492    INTEGER(iwp) ::  jcb    !< fixed child-grid index in the y-direction pointing to the node just behind the
    44784493                            !< boundary-value node
    4479     INTEGER(iwp) ::  jcbc   !< Fixed child-grid index in the y-direction pointing to the boundary-value nodes
    4480     INTEGER(iwp) ::  jcbgp  !< Index running over the redundant boundary ghost points in y-direction
    4481     INTEGER(iwp) ::  jpbeg  !< Parent-grid index in the y-direction pointing to the starting point of workarr_sn
     4494    INTEGER(iwp) ::  jcbc   !< fixed child-grid index in the y-direction pointing to the boundary-value nodes
     4495    INTEGER(iwp) ::  jcbgp  !< index running over the redundant boundary ghost points in y-direction
     4496    INTEGER(iwp) ::  jpbeg  !< parent-grid index in the y-direction pointing to the starting point of workarr_sn
    44824497                            !< in the parent-grid array
    4483     INTEGER(iwp) ::  jpw    !< Reduced parent-grid index in the y-direction for workarr_sn pointing to
     4498    INTEGER(iwp) ::  jpw    !< reduced parent-grid index in the y-direction for workarr_sn pointing to
    44844499                            !< the boundary ghost node
    4485     INTEGER(iwp) ::  jpwp   !< Reduced parent-grid index in the y-direction for workarr_sn pointing to
     4500    INTEGER(iwp) ::  jpwp   !< reduced parent-grid index in the y-direction for workarr_sn pointing to
    44864501                            !< the first prognostic node
    4487     INTEGER(iwp) ::  kc     !< Running child-grid index in the z-direction
    4488     INTEGER(iwp) ::  kp     !< Running parent-grid index in the z-direction
    4489 
    4490     REAL(wp) ::  cb          !< Interpolation coefficient for the boundary ghost node
    4491     REAL(wp) ::  cp          !< Interpolation coefficient for the first prognostic node
    4492     REAL(wp) ::  c_interp_1  !< Value interpolated to the flux point in x direction from the parent-grid data
    4493     REAL(wp) ::  c_interp_2  !< Auxiliary value interpolated  to the flux point in x direction from the parent-grid data
    4494 
     4502    INTEGER(iwp) ::  kc     !< running child-grid index in the z-direction
     4503    INTEGER(iwp) ::  kp     !< running parent-grid index in the z-direction
     4504
     4505    REAL(wp) ::  cb          !< interpolation coefficient for the boundary ghost node
     4506    REAL(wp) ::  cp          !< interpolation coefficient for the first prognostic node
     4507    REAL(wp) ::  c_interp_1  !< value interpolated to the flux point in x direction from the parent-grid data
     4508    REAL(wp) ::  c_interp_2  !< auxiliary value interpolated  to the flux point in x direction from the parent-grid data
    44954509
    44964510!
     
    46924706    IMPLICIT NONE
    46934707
    4694     CHARACTER(LEN=1), INTENT(IN) ::  var  !< Variable symbol: 'u', 'v', 'w' or 's'
    4695 
    4696     INTEGER(iwp), INTENT(IN) ::  kct  !< The parent-grid index in z-direction just below the boundary value node
    4697 
    4698     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< Indicates start index of child cells belonging to certain
     4708    CHARACTER(LEN=1), INTENT(IN) ::  var  !< variable symbol: 'u', 'v', 'w' or 's'
     4709
     4710    INTEGER(iwp), INTENT(IN) ::  kct  !< the parent-grid index in z-direction just below the boundary value node
     4711
     4712    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< indicates start index of child cells belonging to certain
    46994713                                                            !< parent cell - x direction
    4700     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< Indicates end index of child cells belonging to certain
     4714    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< indicates end index of child cells belonging to certain
    47014715                                                            !< parent cell - x direction
    4702     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< Indicates start index of child cells belonging to certain
     4716    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< indicates start index of child cells belonging to certain
    47034717                                                            !< parent cell - y direction
    4704     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< Indicates end index of child cells belonging to certain
     4718    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< indicates end index of child cells belonging to certain
    47054719                                                            !< parent cell - y direction
    47064720
     
    47094723    REAL(wp), DIMENSION(0:pg%nz+1,jps:jpn,ipl:ipr), INTENT(IN) ::  parent_array  !< Parent-grid array
    47104724
    4711 
    47124725!
    47134726!-- Local variables:
    4714     INTEGER(iwp) ::  ic          !< Running child-grid index in the x-direction
     4727    INTEGER(iwp) ::  ic          !< running child-grid index in the x-direction
    47154728    INTEGER(iwp) ::  ierr        !< MPI error code
    4716     INTEGER(iwp) ::  iplc        !< Lower parent-grid index limit in the x-direction for copying parent-grid
     4729    INTEGER(iwp) ::  iplc        !< lower parent-grid index limit in the x-direction for copying parent-grid
    47174730                                 !< array data to workarr_t
    4718     INTEGER(iwp) ::  iprc        !< Upper parent-grid index limit in the x-direction for copying parent-grid
     4731    INTEGER(iwp) ::  iprc        !< upper parent-grid index limit in the x-direction for copying parent-grid
    47194732                                 !< array data to workarr_t
    4720     INTEGER(iwp) ::  jc          !< Running child-grid index in the y-direction
    4721     INTEGER(iwp) ::  jpsc        !< Lower parent-grid index limit in the y-direction for copying parent-grid
     4733    INTEGER(iwp) ::  jc          !< running child-grid index in the y-direction
     4734    INTEGER(iwp) ::  jpsc        !< lower parent-grid index limit in the y-direction for copying parent-grid
    47224735                                 !< array data to workarr_t
    4723     INTEGER(iwp) ::  jpnc        !< Upper parent-grid-index limit in the y-direction for copying parent-grid
     4736    INTEGER(iwp) ::  jpnc        !< upper parent-grid-index limit in the y-direction for copying parent-grid
    47244737                                 !< array data to workarr_t
    4725     INTEGER(iwp) ::  kc          !< Vertical child-grid index fixed to the boundary-value level
    4726     INTEGER(iwp) ::  ip          !< Running parent-grid index in the x-direction
    4727     INTEGER(iwp) ::  jp          !< Running parent-grid index in the y-direction
    4728     INTEGER(iwp) ::  kpw         !< Reduced parent-grid index in the z-direction for workarr_t pointing to
     4738    INTEGER(iwp) ::  kc          !< vertical child-grid index fixed to the boundary-value level
     4739    INTEGER(iwp) ::  ip          !< running parent-grid index in the x-direction
     4740    INTEGER(iwp) ::  jp          !< running parent-grid index in the y-direction
     4741    INTEGER(iwp) ::  kpw         !< reduced parent-grid index in the z-direction for workarr_t pointing to
    47294742                                 !< the boundary ghost node
    47304743
    4731     REAL(wp) ::  c31         !< Interpolation coefficient for the 3rd-order WS scheme
    4732     REAL(wp) ::  c32         !< Interpolation coefficient for the 3rd-order WS scheme
    4733     REAL(wp) ::  c33         !< Interpolation coefficient for the 3rd-order WS scheme
    4734     REAL(wp) ::  c_interp_1  !< Value interpolated to the flux point in z direction from the parent-grid data
    4735     REAL(wp) ::  c_interp_2  !< Auxiliary value interpolated to the flux point in z direction from the parent-grid data
     4744    REAL(wp) ::  c31         !< interpolation coefficient for the 3rd-order WS scheme
     4745    REAL(wp) ::  c32         !< interpolation coefficient for the 3rd-order WS scheme
     4746    REAL(wp) ::  c33         !< interpolation coefficient for the 3rd-order WS scheme
     4747    REAL(wp) ::  c_interp_1  !< value interpolated to the flux point in z direction from the parent-grid data
     4748    REAL(wp) ::  c_interp_2  !< auxiliary value interpolated to the flux point in z direction from the parent-grid data
    47364749
    47374750
     
    49644977    IMPLICIT NONE
    49654978
    4966     CHARACTER(LEN=*), INTENT(IN) ::  var  !< Variable symbol: 'u', 'v', 'w' or 's'
    4967 
    4968     INTEGER(iwp), INTENT(IN) ::  kct  !< Top boundary index for anterpolation along z
     4979    CHARACTER(LEN=*), INTENT(IN) ::  var  !< variable symbol: 'u', 'v', 'w' or 's'
     4980
     4981    INTEGER(iwp), INTENT(IN) ::  kct  !< top boundary index for anterpolation along z
    49694982
    49704983    INTEGER(iwp), DIMENSION(0:pg%nz+1,jpsa:jpna,ipla:ipra), INTENT(IN) ::  ijkfc  !< number of child grid points contributing
    49714984                                                                                  !< to a parent grid box
    4972     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< Indicates start index of child cells belonging to certain
     4985    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifl  !< indicates start index of child cells belonging to certain
    49734986                                                            !< parent cell - x direction
    4974     INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< Indicates end index of child cells belonging to certain
     4987    INTEGER(iwp), DIMENSION(ipla:ipra), INTENT(IN) ::  ifu  !< indicates end index of child cells belonging to certain
    49754988                                                            !< parent cell - x direction
    4976     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< Indicates start index of child cells belonging to certain
     4989    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfl  !< indicates start index of child cells belonging to certain
    49774990                                                            !< parent cell - y direction
    4978     INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< Indicates end index of child cells belonging to certain
     4991    INTEGER(iwp), DIMENSION(jpsa:jpna), INTENT(IN) ::  jfu  !< indicates end index of child cells belonging to certain
    49794992                                                            !< parent cell - y direction
    4980     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< Indicates start index of child cells belonging to certain
     4993    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfl  !< indicates start index of child cells belonging to certain
    49814994                                                            !< parent cell - z direction
    4982     INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< Indicates end index of child cells belonging to certain
     4995    INTEGER(iwp), DIMENSION(0:pg%nz+1), INTENT(IN) ::  kfu  !< indicates end index of child cells belonging to certain
    49834996                                                            !< parent cell - z direction
    49844997
    4985     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg), INTENT(IN) ::  child_array  !< Child-grid array
    4986 
    4987     REAL(wp), DIMENSION(0:pg%nz+1,jps:jpn,ipl:ipr), INTENT(INOUT) ::  parent_array  !< Parent-grid array
     4998    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg), INTENT(IN) ::  child_array  !< child-grid array
     4999
     5000    REAL(wp), DIMENSION(0:pg%nz+1,jps:jpn,ipl:ipr), INTENT(INOUT) ::  parent_array  !< parent-grid array
    49885001
    49895002!
    49905003!-- Local variables:
    4991     INTEGER(iwp) ::  ic              !< Running index x-direction - child grid
    4992     INTEGER(iwp) ::  ip              !< Running index x-direction - parent grid
    4993     INTEGER(iwp) ::  ipl_anterp      !< Left boundary index for anterpolation along x
    4994     INTEGER(iwp) ::  ipr_anterp      !< Right boundary index for anterpolation along x
    4995     INTEGER(iwp) ::  jc              !< Running index y-direction - child grid
    4996     INTEGER(iwp) ::  jp              !< Running index y-direction - parent grid
    4997     INTEGER(iwp) ::  jpn_anterp      !< North boundary index for anterpolation along y
    4998     INTEGER(iwp) ::  jps_anterp      !< South boundary index for anterpolation along y
    4999     INTEGER(iwp) ::  kc              !< Running index z-direction - child grid
    5000     INTEGER(iwp) ::  kp              !< Running index z-direction - parent grid
    5001     INTEGER(iwp) ::  kpt_anterp      !< Top boundary index for anterpolation along z
     5004    INTEGER(iwp) ::  ic              !< running index x-direction - child grid
     5005    INTEGER(iwp) ::  ip              !< running index x-direction - parent grid
     5006    INTEGER(iwp) ::  ipl_anterp      !< left boundary index for anterpolation along x
     5007    INTEGER(iwp) ::  ipr_anterp      !< right boundary index for anterpolation along x
     5008    INTEGER(iwp) ::  jc              !< running index y-direction - child grid
     5009    INTEGER(iwp) ::  jp              !< running index y-direction - parent grid
     5010    INTEGER(iwp) ::  jpn_anterp      !< north boundary index for anterpolation along y
     5011    INTEGER(iwp) ::  jps_anterp      !< south boundary index for anterpolation along y
     5012    INTEGER(iwp) ::  kc              !< running index z-direction - child grid
     5013    INTEGER(iwp) ::  kp              !< running index z-direction - parent grid
     5014    INTEGER(iwp) ::  kpt_anterp      !< top boundary index for anterpolation along z
    50025015    INTEGER(iwp) ::  var_flag        !< bit number used to flag topography on respective grid
    50035016
    5004     REAL(wp) ::  cellsum  !< Sum of respective child cells belonging to parent cell
     5017    REAL(wp) ::  cellsum  !< sum of respective child cells belonging to parent cell
    50055018
    50065019!
     
    50925105    IMPLICIT NONE
    50935106
    5094     INTEGER(iwp) ::  ic  !< Index along x-direction
    5095     INTEGER(iwp) ::  jc  !< Index along y-direction
    5096     INTEGER(iwp) ::  kc  !< Index along z-direction
    5097     INTEGER(iwp) ::  lb  !< Running index for aerosol size bins
    5098     INTEGER(iwp) ::  lc  !< Running index for aerosol mass bins
    5099     INTEGER(iwp) ::  lg  !< Running index for salsa gases
    5100     INTEGER(iwp) ::  m   !< Running index for surface type
    5101     INTEGER(iwp) ::  n   !< Running index for number of chemical species
     5107    INTEGER(iwp) ::  ic  !< index along x-direction
     5108    INTEGER(iwp) ::  jc  !< index along y-direction
     5109    INTEGER(iwp) ::  kc  !< index along z-direction
     5110    INTEGER(iwp) ::  lb  !< running index for aerosol size bins
     5111    INTEGER(iwp) ::  lc  !< running index for aerosol mass bins
     5112    INTEGER(iwp) ::  lg  !< running index for salsa gases
     5113    INTEGER(iwp) ::  m   !< running index for surface type
     5114    INTEGER(iwp) ::  n   !< running index for number of chemical species
    51025115
    51035116
     
    53075320    IMPLICIT NONE
    53085321
    5309     INTEGER(iwp) ::  i     !< Running index in the x-direction
     5322    INTEGER(iwp) ::  i     !< running index in the x-direction
    53105323    INTEGER(iwp) ::  ierr  !< MPI error code
    5311     INTEGER(iwp) ::  j     !< Running index in the y-direction
    5312     INTEGER(iwp) ::  k     !< Running index in the z-direction
    5313     INTEGER(iwp) ::  n     !< Running index over the boundary faces: l, r, s, n and t
    5314 
    5315     REAL(wp) ::  dxdy                  !< Surface area of grid cell top face
    5316     REAL(wp) ::  innor                 !< Inner normal vector of the grid cell face
    5317     REAL(wp) ::  sub_sum               !< Intermediate sum for reducing the loss of signifigant digits in 2-D summations
    5318     REAL(wp) ::  u_corr_left           !< Correction added to the left boundary value of u
    5319     REAL(wp) ::  u_corr_right          !< Correction added to the right boundary value of u
    5320     REAL(wp) ::  v_corr_south          !< Correction added to the south boundary value of v
    5321     REAL(wp) ::  v_corr_north          !< Correction added to the north boundary value of v
    5322     REAL(wp) ::  volume_flux_integral  !< Surface integral of volume flux over the domain boundaries
    5323     REAL(wp) ::  volume_flux_local     !< Surface integral of volume flux over the subdomain boundary face
    5324     REAL(wp) ::  w_corr_top            !< Correction added to the top boundary value of w
    5325 
    5326     REAL(wp), DIMENSION(5) ::  volume_flux  !< Surface integral of volume flux over each boundary face of the domain
    5327 
     5324    INTEGER(iwp) ::  j     !< running index in the y-direction
     5325    INTEGER(iwp) ::  k     !< running index in the z-direction
     5326    INTEGER(iwp) ::  n     !< running index over the boundary faces: l, r, s, n and t
     5327
     5328    REAL(wp) ::  dxdy                  !< surface area of grid cell top face
     5329    REAL(wp) ::  innor                 !< inner normal vector of the grid cell face
     5330    REAL(wp) ::  sub_sum               !< intermediate sum for reducing the loss of signifigant digits in 2-D summations
     5331    REAL(wp) ::  u_corr_left           !< correction added to the left boundary value of u
     5332    REAL(wp) ::  u_corr_right          !< correction added to the right boundary value of u
     5333    REAL(wp) ::  v_corr_south          !< correction added to the south boundary value of v
     5334    REAL(wp) ::  v_corr_north          !< correction added to the north boundary value of v
     5335    REAL(wp) ::  volume_flux_integral  !< surface integral of volume flux over the domain boundaries
     5336    REAL(wp) ::  volume_flux_local     !< surface integral of volume flux over the subdomain boundary face
     5337    REAL(wp) ::  w_corr_top            !< correction added to the top boundary value of w
     5338
     5339    REAL(wp), DIMENSION(5) ::  volume_flux  !< surface integral of volume flux over each boundary face of the domain
    53285340
    53295341!
     
    55345546    IMPLICIT NONE
    55355547
    5536     INTEGER(iwp) ::  i     !< Running index in the x-direction
     5548    INTEGER(iwp) ::  i     !< running index in the x-direction
    55375549    INTEGER(iwp) ::  ierr  !< MPI error code
    5538     INTEGER(iwp) ::  j     !< Running index in the y-direction
    5539     INTEGER(iwp) ::  k     !< Running index in the z-direction
    5540 
    5541     REAL(wp) ::  dxdy               !< Surface area of grid cell top face
    5542     REAL(wp) ::  sub_sum            !< Intermediate sum for reducing the loss of signifigant digits in 2-D summations
    5543     REAL(wp) ::  top_area           !< Top boundary face area
    5544     REAL(wp) ::  volume_flux        !< Surface integral of volume flux over the top boundary face
    5545     REAL(wp) ::  volume_flux_local  !< Surface integral of volume flux over the subdomain boundary face
    5546     REAL(wp) ::  w_corr_top         !< Correction added to the top boundary value of w
     5550    INTEGER(iwp) ::  j     !< running index in the y-direction
     5551    INTEGER(iwp) ::  k     !< running index in the z-direction
     5552
     5553    REAL(wp) ::  dxdy               !< surface area of grid cell top face
     5554    REAL(wp) ::  sub_sum            !< intermediate sum for reducing the loss of signifigant digits in 2-D summations
     5555    REAL(wp) ::  top_area           !< top boundary face area
     5556    REAL(wp) ::  volume_flux        !< surface integral of volume flux over the top boundary face
     5557    REAL(wp) ::  volume_flux_local  !< surface integral of volume flux over the subdomain boundary face
     5558    REAL(wp) ::  w_corr_top         !< correction added to the top boundary value of w
    55475559
    55485560
Note: See TracChangeset for help on using the changeset viewer.