Changeset 4414


Ignore:
Timestamp:
Feb 19, 2020 8:16:04 PM (4 years ago)
Author:
suehring
Message:

Remove deprecated topography arrays; Move basic initialization of numerics into an extra module interface

Location:
palm/trunk/SOURCE
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r4411 r4414  
    2525# -----------------
    2626# $Id$
     27# Move dependencies for init grid from advection scheme and multigrid solver
     28# to module_interface
     29#
     30# 4411 2020-02-18 14:28:02Z maronga
    2731# Added output routines for WTM
    2832#
     
    664668        vertical_nesting_mod.o
    665669init_grid.o: \
    666         advec_ws.o \
    667         mod_kinds.o \
    668         modules.o \
    669         netcdf_data_input_mod.o \
    670         netcdf_interface_mod.o \
    671         poismg_noopt_mod.o \
    672         surface_mod.o \
     670        mod_kinds.o \
     671        modules.o \
     672        netcdf_data_input_mod.o \
     673        netcdf_interface_mod.o \
    673674        vertical_nesting_mod.o
    674675init_masks.o: \
     
    769770        ocean_mod.o \
    770771        plant_canopy_model_mod.o \
     772        poismg_noopt_mod.o \
    771773        radiation_model_mod.o \
    772774        salsa_mod.o \
    773775        spectra_mod.o \
    774776        surface_data_output_mod.o \
     777        surface_mod.o \
    775778        synthetic_turbulence_generator_mod.o \
    776779        turbulence_closure_mod.o \
  • palm/trunk/SOURCE/advec_ws.f90

    r4360 r4414  
    2525! -----------------
    2626! $Id$
     27! Move call for initialization of control flags to ws_init
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    379382
    380383       ENDIF
     384!
     385!--    Initialize the flag arrays controlling degradation near walls, i.e.
     386!--    to decrease the numerical stencil appropriately. The order of the scheme
     387!--    is degraded near solid walls as well as near non-cyclic inflow and outflow
     388!--    boundaries. Do this separately for momentum and scalars.
     389       IF ( ws_scheme_mom )  CALL ws_init_flags_momentum
     390
     391       IF ( ws_scheme_sca )  THEN
     392          ALLOCATE( advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     393          advc_flags_s = 0
     394          CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l,     &
     395                                     bc_dirichlet_n  .OR.  bc_radiation_n,     &
     396                                     bc_dirichlet_r  .OR.  bc_radiation_r,     &
     397                                     bc_dirichlet_s  .OR.  bc_radiation_s,     &
     398                                     advc_flags_s )
     399       ENDIF
    381400
    382401    END SUBROUTINE ws_init
     
    398417       INTEGER(iwp) ::  k_pp  !< dummy index along z
    399418       INTEGER(iwp) ::  k_ppp !< dummy index along z
    400        
     419
    401420       LOGICAL      ::  flag_set !< steering variable for advection flags
    402    
     421
     422       ALLOCATE( advc_flags_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    403423       advc_flags_m = 0
    404 
    405424!
    406425!--    Set advc_flags_m to steer the degradation of the advection scheme in advec_ws
     
    850869       INTEGER(iwp) ::  k_pp  !< dummy index along z
    851870       INTEGER(iwp) ::  k_ppp !< dummy index along z
    852        
     871
    853872       INTEGER(iwp), INTENT(INOUT), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::&
    854873                                                  advc_flag !< flag array to control order of scalar advection
    855        
     874
    856875       LOGICAL ::  flag_set     !< steering variable for advection flags
    857876       LOGICAL ::  non_cyclic_l !< flag that indicates non-cyclic boundary on the left
     
    859878       LOGICAL ::  non_cyclic_r !< flag that indicates non-cyclic boundary on the right
    860879       LOGICAL ::  non_cyclic_s !< flag that indicates non-cyclic boundary on the south
    861        
     880
    862881       LOGICAL, OPTIONAL ::  extensive_degrad !< flag indicating that extensive degradation is required, e.g. for
    863882                                              !< passive scalars nearby topography along the horizontal directions,
  • palm/trunk/SOURCE/init_grid.f90

    r4386 r4414  
    2525! -----------------
    2626! $Id$
     27! - Remove deprecated topography arrays nzb_s_inner, nzb_u_inner, etc.
     28! - Move initialization of boundary conditions and multigrid into an extra
     29!   module interface.
     30!
     31! 4386 2020-01-27 15:07:30Z Giersch
    2732! Allocation statements, comments, naming of variables revised and _wp added to
    2833! real type values
     
    123128!------------------------------------------------------------------------------!
    124129 SUBROUTINE init_grid
    125  
    126     USE advec_ws,                                                              &
    127         ONLY:  ws_init_flags_momentum, ws_init_flags_scalar
    128130
    129131    USE arrays_3d,                                                             &
    130132        ONLY:  dd2zu, ddzu, ddzu_pres, ddzw, dzu, dzw, x, xu, y, yv, zu, zw
    131        
     133
    132134    USE control_parameters,                                                    &
    133         ONLY:  bc_lr_cyc, bc_ns_cyc,                                           &
    134                bc_dirichlet_l,                                                 &
    135                bc_dirichlet_n,                                                 &
    136                bc_dirichlet_r,                                                 &
    137                bc_dirichlet_s,                                                 &
    138                bc_radiation_l,                                                 &
    139                bc_radiation_n,                                                 &
    140                bc_radiation_r,                                                 &
    141                bc_radiation_s,                                                 &
    142                constant_flux_layer, dz, dz_max, dz_stretch_factor,             &
     135        ONLY:  constant_flux_layer, dz, dz_max, dz_stretch_factor,             &
    143136               dz_stretch_factor_array, dz_stretch_level, dz_stretch_level_end,&
    144137               dz_stretch_level_end_index, dz_stretch_level_start_index,       &
    145138               dz_stretch_level_start, ibc_uv_b, message_string,               &
    146                momentum_advec, number_stretch_level_end,                       &
    147                number_stretch_level_start, ocean_mode, psolver, scalar_advec,  &
    148                symmetry_flag, topography, use_surface_fluxes
    149          
     139               number_stretch_level_end,                                       &
     140               number_stretch_level_start,                                     &
     141               ocean_mode,                                                     &
     142               psolver,                                                        &
     143               symmetry_flag,                                                  &
     144               topography,                                                     &
     145               use_surface_fluxes
     146
    150147    USE grid_variables,                                                        &
    151148        ONLY:  ddx, ddx2, ddy, ddy2, dx, dx2, dy, dy2, zu_s_inner, zw_w_inner
    152        
     149
    153150    USE indices,                                                               &
    154         ONLY:  advc_flags_m,                                                   &
    155                advc_flags_s,                                                   &
    156                nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz,   &
    157                nzb, nzb_diff, nzb_diff_s_inner, nzb_diff_s_outer,              &
    158                nzb_max, nzb_s_inner, nzb_s_outer, nzb_u_inner,                 &
    159                nzb_u_outer, nzb_v_inner, nzb_v_outer, nzb_w_inner,             &
    160                nzb_w_outer, nzt, topo_top_ind, topo_min_level
    161    
     151        ONLY:  nbgp,                                                           &
     152               nx,                                                             &
     153               nxl,                                                            &
     154               nxlg,                                                           &
     155               nxr,                                                            &
     156               nxrg,                                                           &
     157               ny,                                                             &
     158               nyn,                                                            &
     159               nyng,                                                           &
     160               nys,                                                            &
     161               nysg,                                                           &
     162               nz,                                                             &
     163               nzb,                                                            &
     164               nzb_diff,                                                       &
     165               nzb_max,                                                        &
     166               nzt,                                                            &
     167               topo_top_ind,                                                   &
     168               topo_min_level
     169
    162170    USE kinds
    163171
    164172    USE pegrid
    165 
    166     USE poismg_noopt_mod
    167 
    168     USE surface_mod,                                                           &
    169         ONLY:  init_bc
    170173
    171174    USE vertical_nesting_mod,                                                  &
     
    182185    INTEGER(iwp) ::  nzb_local_max !< vertical grid index of maximum topography height
    183186    INTEGER(iwp) ::  nzb_local_min !< vertical grid index of minimum topography height
    184                                      
    185     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_local  !< index for topography top at cell-center
    186     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_tmp    !< dummy to calculate topography indices on u- and v-grid
    187187
    188188    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo !< input array for 3D topography and dummy array for setting "outer"-flags
     
    644644!
    645645!-- Set flags to mask topography on the grid.
    646     CALL set_topo_flags( topo )   
    647 !
    648 !-- Calculate wall flag arrays for the multigrid method.
    649 !-- Please note, wall flags are only applied in the non-optimized version.
    650     IF ( psolver == 'multigrid_noopt' )  CALL poismg_noopt_init
    651 
    652 !
    653 !-- Init flags for ws-scheme to degrade order of the numerics near walls, i.e.
    654 !-- to decrease the numerical stencil appropriately. The order of the scheme
    655 !-- is degraded near solid walls as well as near non-cyclic inflow and outflow
    656 !-- boundaries. Do this separately for momentum and scalars.
    657     IF ( momentum_advec == 'ws-scheme' )  THEN
    658        ALLOCATE( advc_flags_m(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    659        CALL ws_init_flags_momentum
    660     ENDIF
    661     IF ( scalar_advec == 'ws-scheme'   )  THEN
    662        ALLOCATE( advc_flags_s(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
    663        advc_flags_s = 0
    664        
    665        CALL ws_init_flags_scalar( bc_dirichlet_l  .OR.  bc_radiation_l,        &
    666                                   bc_dirichlet_n  .OR.  bc_radiation_n,        &
    667                                   bc_dirichlet_r  .OR.  bc_radiation_r,        &
    668                                   bc_dirichlet_s  .OR.  bc_radiation_s,        &
    669                                   advc_flags_s )
    670     ENDIF
     646    CALL set_topo_flags( topo )
    671647
    672648!
     
    704680    topo_min_level = MINVAL( topo_top_ind(nys:nyn,nxl:nxr,0) )
    705681#endif
    706 !
    707 !-- Initialize boundary conditions via surface type
    708     CALL init_bc
    709 
    710 !
    711 !-- Allocate and set topography height arrays required for data output
    712     IF ( TRIM( topography ) /= 'flat' )  THEN
    713 !
    714 !--    Allocate and set the arrays containing the topography height
    715        IF ( nxr == nx  .AND.  nyn /= ny )  THEN
    716           ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn) )                             
    717           ALLOCATE( zw_w_inner(nxl:nxr+1,nys:nyn) )
    718        ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
    719           ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn+1) )                             
    720           ALLOCATE( zw_w_inner(nxl:nxr,nys:nyn+1) )
    721        ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
    722           ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn+1) )
    723           ALLOCATE( zw_w_inner(nxl:nxr+1,nys:nyn+1) )
    724        ELSE
    725           ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn) )
    726           ALLOCATE( zw_w_inner(nxl:nxr,nys:nyn) )
    727        ENDIF
    728 
    729        zu_s_inner   = 0.0_wp
    730        zw_w_inner   = 0.0_wp
    731 !
    732 !--    Determine local topography height on scalar and w-grid. Note, setting
    733 !--    lateral boundary values is not necessary, realized via wall_flags_static_0
    734 !--    array. Further, please note that loop bounds are different from
    735 !--    nxl to nxr and nys to nyn on south and right model boundary, hence,
    736 !--    use intrinsic lbound and ubound functions to infer array bounds.
    737        DO  i = LBOUND(zu_s_inner, 1), UBOUND(zu_s_inner, 1)
    738           DO  j = LBOUND(zu_s_inner, 2), UBOUND(zu_s_inner, 2)
    739 !
    740 !--          Topography height on scalar grid. Therefore, determine index of
    741 !--          upward-facing surface element on scalar grid.
    742              zu_s_inner(i,j) = zu(topo_top_ind(j,i,0))
    743 !
    744 !--          Topography height on w grid. Therefore, determine index of
    745 !--          upward-facing surface element on w grid.
    746              zw_w_inner(i,j) = zw(topo_top_ind(j,i,3))
    747           ENDDO
    748        ENDDO
    749     ENDIF
    750 
    751 !
    752 !-- In the following, calculate 2D index arrays. Note, these will be removed
    753 !-- soon.
    754 !-- Allocate outer and inner index arrays for topography and set
    755 !-- defaults.                   
    756     ALLOCATE( nzb_s_inner(nysg:nyng,nxlg:nxrg) )                               
    757     ALLOCATE( nzb_s_outer(nysg:nyng,nxlg:nxrg) )                               
    758     ALLOCATE( nzb_u_inner(nysg:nyng,nxlg:nxrg) )                               
    759     ALLOCATE( nzb_u_outer(nysg:nyng,nxlg:nxrg) )                               
    760     ALLOCATE( nzb_v_inner(nysg:nyng,nxlg:nxrg) )                               
    761     ALLOCATE( nzb_v_outer(nysg:nyng,nxlg:nxrg) )                               
    762     ALLOCATE( nzb_w_inner(nysg:nyng,nxlg:nxrg) )                               
    763     ALLOCATE( nzb_w_outer(nysg:nyng,nxlg:nxrg) )                               
    764     ALLOCATE( nzb_diff_s_inner(nysg:nyng,nxlg:nxrg) )                         
    765     ALLOCATE( nzb_diff_s_outer(nysg:nyng,nxlg:nxrg) )                         
    766     ALLOCATE( nzb_local(nysg:nyng,nxlg:nxrg) )                                 
    767     ALLOCATE( nzb_tmp(nysg:nyng,nxlg:nxrg) )
    768 !
    769 !-- Initialize 2D-index arrays. Note, these will be removed soon!
    770     nzb_local(nys:nyn,nxl:nxr) = topo_top_ind(nys:nyn,nxl:nxr,0)
    771     CALL exchange_horiz_2d_int( nzb_local, nys, nyn, nxl, nxr, nbgp )
     682
    772683!
    773684!-- Check topography for consistency with model domain. Therefore, use
     
    792703       ENDIF
    793704    ENDIF
    794 
    795     nzb_s_inner = nzb;  nzb_s_outer = nzb
    796     nzb_u_inner = nzb;  nzb_u_outer = nzb
    797     nzb_v_inner = nzb;  nzb_v_outer = nzb
    798     nzb_w_inner = nzb;  nzb_w_outer = nzb
    799 
    800705!
    801706!-- Define vertical gridpoint from (or to) which on the usual finite difference
     
    807712    ENDIF
    808713
    809     nzb_diff_s_inner = nzb_diff;  nzb_diff_s_outer = nzb_diff
    810 !
    811 !-- Set Neumann conditions for topography. Will be removed soon.
    812     IF ( .NOT. bc_ns_cyc )  THEN
    813        IF ( nys == 0  )  THEN
    814           DO  i = 1, nbgp 
    815              nzb_local(nys-i,:)   = nzb_local(nys,:)
    816           ENDDO
    817        ELSEIF ( nyn == ny )  THEN
    818           DO  i = 1, nbgp 
    819              nzb_local(ny+i,:) = nzb_local(ny,:)
    820           ENDDO
    821        ENDIF
    822     ENDIF
    823 
    824     IF ( .NOT. bc_lr_cyc )  THEN
    825        IF ( nxl == 0  )  THEN
    826           DO  i = 1, nbgp 
    827              nzb_local(:,nxl-i)   = nzb_local(:,nxl)
    828           ENDDO
    829        ELSEIF ( nxr == nx )  THEN
    830           DO  i = 1, nbgp 
    831              nzb_local(:,nx+i) = nzb_local(:,nx)
    832           ENDDO
    833        ENDIF         
    834     ENDIF
    835 !
    836 !-- Initialization of 2D index arrays, will be removed soon!
    837 !-- Initialize nzb_s_inner and nzb_w_inner
    838     nzb_s_inner = nzb_local
    839     nzb_w_inner = nzb_local
    840 
    841 !
    842 !-- Initialize remaining index arrays:
    843 !-- first pre-initialize them with nzb_s_inner...
    844     nzb_u_inner = nzb_s_inner
    845     nzb_u_outer = nzb_s_inner
    846     nzb_v_inner = nzb_s_inner
    847     nzb_v_outer = nzb_s_inner
    848     nzb_w_outer = nzb_s_inner
    849     nzb_s_outer = nzb_s_inner
    850 
    851 !
    852 !-- nzb_s_outer:
    853 !-- extend nzb_local east-/westwards first, then north-/southwards
    854     nzb_tmp = nzb_local
    855     DO  j = nys, nyn
    856        DO  i = nxl, nxr
    857           nzb_tmp(j,i) = MAX( nzb_local(j,i-1), nzb_local(j,i),             &
    858                               nzb_local(j,i+1) )
     714    IF ( TRIM( topography ) /= 'flat' )  THEN
     715!
     716!--    Allocate and set the arrays containing the topography height (for output
     717!--    reasons only).
     718       IF ( nxr == nx  .AND.  nyn /= ny )  THEN
     719          ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn),                             &
     720                    zw_w_inner(nxl:nxr+1,nys:nyn) )
     721       ELSEIF ( nxr /= nx  .AND.  nyn == ny )  THEN
     722          ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn+1),                             &
     723                    zw_w_inner(nxl:nxr,nys:nyn+1) )
     724       ELSEIF ( nxr == nx  .AND.  nyn == ny )  THEN
     725          ALLOCATE( zu_s_inner(nxl:nxr+1,nys:nyn+1),                           &
     726                    zw_w_inner(nxl:nxr+1,nys:nyn+1) )
     727       ELSE
     728          ALLOCATE( zu_s_inner(nxl:nxr,nys:nyn),                               &
     729                    zw_w_inner(nxl:nxr,nys:nyn) )
     730       ENDIF
     731
     732       zu_s_inner   = 0.0_wp
     733       zw_w_inner   = 0.0_wp
     734!
     735!--    Determine local topography height on scalar and w-grid. Note, setting
     736!--    lateral boundary values is not necessary, realized via wall_flags_static_0
     737!--    array. Further, please note that loop bounds are different from
     738!--    nxl to nxr and nys to nyn on south and right model boundary, hence,
     739!--    use intrinsic lbound and ubound functions to infer array bounds.
     740       DO  i = LBOUND(zu_s_inner, 1), UBOUND(zu_s_inner, 1)
     741          DO  j = LBOUND(zu_s_inner, 2), UBOUND(zu_s_inner, 2)
     742!
     743!--          Topography height on scalar grid. Therefore, determine index of
     744!--          upward-facing surface element on scalar grid.
     745             zu_s_inner(i,j) = zu(topo_top_ind(j,i,0))
     746!
     747!--          Topography height on w grid. Therefore, determine index of
     748!--          upward-facing surface element on w grid.
     749             zw_w_inner(i,j) = zw(topo_top_ind(j,i,3))
     750          ENDDO
    859751       ENDDO
    860     ENDDO
    861        
    862     CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )
    863      
    864     DO  i = nxl, nxr
    865        DO  j = nys, nyn
    866           nzb_s_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i),             &
    867                                   nzb_tmp(j+1,i) )
    868        ENDDO
    869 !
    870 !--    non-cyclic boundary conditions (overwritten by call of
    871 !--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
    872        IF ( nys == 0 )  THEN
    873           j = -1
    874           nzb_s_outer(j,i) = MAX( nzb_tmp(j+1,i), nzb_tmp(j,i) )
    875        ENDIF
    876        IF ( nyn == ny )  THEN
    877           j = ny + 1
    878           nzb_s_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i) )
    879        ENDIF
    880     ENDDO
    881 !
    882 !-- nzb_w_outer:
    883 !-- identical to nzb_s_outer
    884     nzb_w_outer = nzb_s_outer
    885 !
    886 !-- nzb_u_inner:
    887 !-- extend nzb_local rightwards only
    888     nzb_tmp = nzb_local
    889     DO  j = nys, nyn
    890        DO  i = nxl, nxr
    891           nzb_tmp(j,i) = MAX( nzb_local(j,i-1), nzb_local(j,i) )
    892        ENDDO
    893     ENDDO
    894        
    895     CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )
    896        
    897     nzb_u_inner = nzb_tmp
    898 !
    899 !-- nzb_u_outer:
    900 !-- extend current nzb_tmp (nzb_u_inner) north-/southwards
    901     DO  i = nxl, nxr
    902        DO  j = nys, nyn
    903           nzb_u_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i),             &
    904                                   nzb_tmp(j+1,i) )
    905        ENDDO
    906 !
    907 !--    non-cyclic boundary conditions (overwritten by call of
    908 !--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
    909        IF ( nys == 0 )  THEN
    910           j = -1
    911           nzb_u_outer(j,i) = MAX( nzb_tmp(j+1,i), nzb_tmp(j,i) )
    912        ENDIF
    913        IF ( nyn == ny )  THEN
    914           j = ny + 1
    915           nzb_u_outer(j,i) = MAX( nzb_tmp(j-1,i), nzb_tmp(j,i) )
    916        ENDIF
    917     ENDDO
    918 
    919 !
    920 !-- nzb_v_inner:
    921 !-- extend nzb_local northwards only
    922     nzb_tmp = nzb_local
    923     DO  i = nxl, nxr
    924        DO  j = nys, nyn
    925           nzb_tmp(j,i) = MAX( nzb_local(j-1,i), nzb_local(j,i) )
    926        ENDDO
    927     ENDDO
    928        
    929     CALL exchange_horiz_2d_int( nzb_tmp, nys, nyn, nxl, nxr, nbgp )     
    930     nzb_v_inner = nzb_tmp
    931 
    932 !
    933 !-- nzb_v_outer:
    934 !-- extend current nzb_tmp (nzb_v_inner) right-/leftwards
    935     DO  j = nys, nyn
    936        DO  i = nxl, nxr
    937           nzb_v_outer(j,i) = MAX( nzb_tmp(j,i-1), nzb_tmp(j,i),                &
    938                                   nzb_tmp(j,i+1) )
    939        ENDDO
    940 !
    941 !--    non-cyclic boundary conditions (overwritten by call of
    942 !--    exchange_horiz_2d_int below in case of cyclic boundary conditions)
    943        IF ( nxl == 0 )  THEN
    944           i = -1
    945           nzb_v_outer(j,i) = MAX( nzb_tmp(j,i+1), nzb_tmp(j,i) )
    946        ENDIF
    947        IF ( nxr == nx )  THEN
    948           i = nx + 1
    949           nzb_v_outer(j,i) = MAX( nzb_tmp(j,i-1), nzb_tmp(j,i) )
    950        ENDIF
    951     ENDDO
    952 
    953 !
    954 !-- Exchange of lateral boundary values (parallel computers) and cyclic
    955 !-- boundary conditions, if applicable.
    956 !-- Since nzb_s_inner and nzb_w_inner are derived directly from nzb_local
    957 !-- they do not require exchange and are not included here.
    958     CALL exchange_horiz_2d_int( nzb_u_inner, nys, nyn, nxl, nxr, nbgp )
    959     CALL exchange_horiz_2d_int( nzb_u_outer, nys, nyn, nxl, nxr, nbgp )
    960     CALL exchange_horiz_2d_int( nzb_v_inner, nys, nyn, nxl, nxr, nbgp )
    961     CALL exchange_horiz_2d_int( nzb_v_outer, nys, nyn, nxl, nxr, nbgp )
    962     CALL exchange_horiz_2d_int( nzb_w_outer, nys, nyn, nxl, nxr, nbgp )
    963     CALL exchange_horiz_2d_int( nzb_s_outer, nys, nyn, nxl, nxr, nbgp )
    964 
    965 !
    966 !-- Set the individual index arrays which define the k index from which on
    967 !-- the usual finite difference form (which does not use surface fluxes) is
    968 !-- applied
    969     IF ( constant_flux_layer  .OR.  use_surface_fluxes )  THEN
    970        nzb_diff_s_inner   = nzb_s_inner + 2
    971        nzb_diff_s_outer   = nzb_s_outer + 2
    972     ELSE
    973        nzb_diff_s_inner   = nzb_s_inner + 1
    974        nzb_diff_s_outer   = nzb_s_outer + 1
    975752    ENDIF
    976753!
     
    27982575                                    BTEST( wall_flags_total_0(:,:,:), ibit )   &
    27992576                                       ), DIM = 1                              &
    2800                                 ) - 1                           
    2801        
     2577                                ) - 1
     2578
    28022579 END SUBROUTINE set_topo_flags
    28032580
    28042581
    28052582
     2583
  • palm/trunk/SOURCE/module_interface.f90

    r4411 r4414  
    2525! -----------------
    2626! $Id$
     27! Add module interface for basic initialization of numerics.
     28!
     29! 4411 2020-02-18 14:28:02Z maronga
    2730! Added output routines for WTM
    2831!
     
    425428        ONLY:  particle_advection
    426429
     430    USE poismg_noopt_mod,                                                      &
     431        ONLY:  poismg_noopt_init
     432
    427433    USE plant_canopy_model_mod,                                                &
    428434         ONLY: pcm_parin,                                                      &
     
    487493               surface_data_output_wrd_global
    488494
     495    USE surface_mod,                                                           &
     496        ONLY:  init_bc
     497
    489498    USE synthetic_turbulence_generator_mod,                                    &
    490499        ONLY:  stg_parin,                                                      &
     
    562571       module_interface_init,                                                  &
    563572       module_interface_init_checks,                                           &
     573       module_interface_init_numerics,                                         &
    564574       module_interface_init_output,                                           &
    565575       module_interface_header,                                                &
     
    620630       MODULE PROCEDURE module_interface_init_checks
    621631    END INTERFACE module_interface_init_checks
     632
     633    INTERFACE module_interface_init_numerics
     634       MODULE PROCEDURE module_interface_init_numerics
     635    END INTERFACE module_interface_init_numerics
    622636
    623637    INTERFACE module_interface_init_output
     
    11101124! Description:
    11111125! ------------
     1126!> Initialize boundary conditions and numerical schemes.
     1127!------------------------------------------------------------------------------!
     1128 SUBROUTINE module_interface_init_numerics
     1129
     1130!
     1131!-- Initialize boundary conditions via surface type
     1132    CALL init_bc
     1133!
     1134!-- Calculate wall flag arrays for the multigrid method.
     1135!-- Please note, wall flags are only applied in the non-optimized version.
     1136    CALL poismg_noopt_init
     1137 
     1138 END SUBROUTINE module_interface_init_numerics
     1139
     1140 
     1141!------------------------------------------------------------------------------!
     1142! Description:
     1143! ------------
    11121144!> Initialize data output
    11131145!------------------------------------------------------------------------------!
  • palm/trunk/SOURCE/modules.f90

    r4360 r4414  
    2525! -----------------
    2626! $Id$
     27! - nzb_diff_s_inner, nzb_diff_s_outer, nzb_inner,nzb_outer, nzb_s_inner,
     28!   nzb_s_outer, nzb_u_inner, nzb_u_outer, nzb_v_inner, nzb_v_outer,
     29!   nzb_w_inner, nzb_w_outer
     30!
     31!
     32! 4360 2020-01-07 11:25:50Z suehring
    2733! Introduction of wall_flags_total_0, which currently sets bits based on static
    2834! topography information used in wall_flags_static_0
     
    10331039    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zu_s_inner  !< height of topography top on scalar grid
    10341040    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  zw_w_inner  !< height of topography top on w grid
    1035                                              
     1041
    10361042    SAVE
    10371043
     
    10931099    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  ngp_2dh_s_inner   !< number of horizontal grid points which are non-topography
    10941100    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  mg_loc_ind        !< internal array to store index bounds of all PEs of that multigrid level where data is collected to PE0
    1095     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_diff_s_inner  !< will be removed
    1096     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_diff_s_outer  !< will be removed
    1097     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_inner         !< will be removed
    1098     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_outer         !< will be removed
    1099     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_s_inner       !< will be removed
    1100     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_s_outer       !< will be removed
    1101     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_u_inner       !< will be removed
    1102     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_u_outer       !< will be removed
    1103     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_v_inner       !< will be removed
    1104     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_v_outer       !< will be removed
    1105     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_w_inner       !< will be removed
    1106     INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nzb_w_outer       !< will be removed
    11071101
    11081102    INTEGER(iwp), DIMENSION(:,:,:), POINTER ::  flags  !< pointer to wall_flags_1-10
  • palm/trunk/SOURCE/palm.f90

    r4400 r4414  
    2525! -----------------
    2626! $Id$
     27! Call to module_interface_init_numerics
     28!
     29! 4400 2020-02-10 20:32:41Z suehring
    2730! Add interface to initialize data output with dom
    2831!
     
    9396
    9497    USE module_interface,                                                      &
    95         ONLY:  module_interface_init_output,                                   &
     98        ONLY:  module_interface_init_numerics,                                 &
     99               module_interface_init_output,                                   &
    96100               module_interface_last_actions
    97101
     
    112116        ONLY:  nested_run, pmci_child_initialize, pmci_init,                   &
    113117               pmci_modelconfiguration, pmci_parent_initialize
    114                
     118
    115119    USE surface_data_output_mod,                                               &
    116120        ONLY:  surface_data_output_last_action
     
    261265!-- topography information if required
    262266    CALL init_grid
     267!
     268!-- Initialize boundary conditions and numerics such as the multigrid solver or
     269!-- the advection routine
     270    CALL module_interface_init_numerics
    263271!
    264272!-- Read global attributes if available. 
  • palm/trunk/SOURCE/poismg_noopt_mod.f90

    r4360 r4414  
    2525! -----------------
    2626! $Id$
     27! Remove double-declared use only construct.
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    8487
    8588    SUBROUTINE poismg_noopt( r )
    86    
    8789
    8890       USE arrays_3d,                                                          &
    8991           ONLY:  d, p_loc
    90 
    91        USE control_parameters,                                                 &
    92            ONLY:  bc_lr_cyc, bc_ns_cyc, gathered_size, grid_level_count,       &
    93                   ibc_p_t, maximum_grid_level, message_string, mgcycles,       &
    94                   mg_cycles, mg_switch_to_pe0_level, residual_limit,           &
    95                   subdomain_size
    9692
    9793       USE control_parameters,                                                 &
     
    16551651
    16561652       USE control_parameters,                                                 &
    1657            ONLY:  bc_lr_cyc, bc_ns_cyc, masking_method, maximum_grid_level
     1653           ONLY:  bc_lr_cyc, bc_ns_cyc, masking_method, maximum_grid_level,    &
     1654                  psolver
    16581655
    16591656       USE indices,                                                            &
     
    16781675
    16791676       INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  topo_tmp
     1677
     1678       IF ( psolver /= 'multigrid_noopt' )  RETURN
    16801679!
    16811680!--    Gridpoint increment of the current level.
Note: See TracChangeset for help on using the changeset viewer.