Changeset 3887 for palm/trunk/SOURCE


Ignore:
Timestamp:
Apr 12, 2019 8:47:41 AM (5 years ago)
Author:
schwenkel
Message:

bugfix for chemistry_model_mod via introducing module_interface_exchange_horiz

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

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

    r3885 r3887  
    2525! -----------------
    2626! $Id$
     27! Added bcm_exchange_horiz which is called after non_transport_physics
     28!
     29! 3885 2019-04-11 11:29:34Z kanani
    2730! Changes related to global restructuring of location messages and introduction
    2831! of additional debug messages
     
    260263
    261264    USE indices,                                                               &
    262         ONLY:  nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt,           &
     265        ONLY:  nbgp, nxl, nxlg, nxr, nxrg, nys, nysg, nyn, nyng, nzb, nzt,     &
    263266               wall_flags_0
    264267
     
    369372           bcm_actions, &
    370373           bcm_non_transport_physics, &
     374           bcm_exchange_horiz, &
    371375           bcm_prognostic_equations, &
    372376           bcm_3d_data_averaging, &
     
    432436       MODULE PROCEDURE bcm_non_transport_physics_ij
    433437    END INTERFACE bcm_non_transport_physics
     438
     439    INTERFACE bcm_exchange_horiz
     440       MODULE PROCEDURE bcm_exchange_horiz
     441    END INTERFACE bcm_exchange_horiz   
    434442
    435443    INTERFACE bcm_prognostic_equations
     
    13121320
    13131321    END SUBROUTINE bcm_non_transport_physics_ij
     1322   
     1323   
     1324!------------------------------------------------------------------------------!
     1325! Description:
     1326! ------------
     1327!> Control of microphysics for all grid points
     1328!------------------------------------------------------------------------------!
     1329    SUBROUTINE bcm_exchange_horiz
     1330
     1331
     1332       IF ( .NOT. microphysics_sat_adjust  .AND.                                &
     1333            ( intermediate_timestep_count == 1  .OR.                            &
     1334              call_microphysics_at_all_substeps ) )                             &
     1335       THEN
     1336          IF ( microphysics_morrison )  THEN
     1337             CALL exchange_horiz( nc, nbgp )
     1338             CALL exchange_horiz( qc, nbgp )         
     1339          ENDIF
     1340          IF ( microphysics_seifert ) THEN
     1341             CALL exchange_horiz( qr, nbgp )
     1342             CALL exchange_horiz( nr, nbgp )
     1343          ENDIF
     1344          CALL exchange_horiz( q, nbgp )
     1345          CALL exchange_horiz( pt, nbgp )         
     1346       ENDIF
     1347
     1348
     1349    END SUBROUTINE bcm_exchange_horiz
     1350   
    13141351
    13151352
     
    28982935       CALL cpu_log( log_point_s(50), 'adjust_cloud', 'start' )
    28992936
    2900        DO  i = nxlg, nxrg
    2901           DO  j = nysg, nyng
     2937       DO  i = nxl, nxr
     2938          DO  j = nys, nyn
    29022939             DO  k = nzb+1, nzt
    29032940!
     
    30203057       CALL cpu_log( log_point_s(65), 'activation', 'start' )
    30213058
    3022        DO  i = nxlg, nxrg
    3023           DO  j = nysg, nyng
     3059       DO  i = nxl, nxr
     3060          DO  j = nys, nyn
    30243061             DO  k = nzb+1, nzt
    30253062!
     
    32213258       CALL cpu_log( log_point_s(66), 'condensation', 'start' )
    32223259
    3223        DO  i = nxlg, nxrg
    3224           DO  j = nysg, nyng
     3260       DO  i = nxl, nxr
     3261          DO  j = nys, nyn
    32253262             DO  k = nzb+1, nzt
    32263263!
     
    33813418       CALL cpu_log( log_point_s(47), 'autoconversion', 'start' )
    33823419
    3383        DO  i = nxlg, nxrg
    3384           DO  j = nysg, nyng
     3420       DO  i = nxl, nxr
     3421          DO  j = nys, nyn
    33853422             DO  k = nzb+1, nzt
    33863423!
     
    36153652       REAL(wp)    ::  flag        !< flag to mask topography grid points
    36163653
    3617        DO  i = nxlg, nxrg
    3618           DO  j = nysg, nyng
     3654       DO  i = nxl, nxr
     3655          DO  j = nys, nyn
    36193656!
    36203657!--          Determine vertical index of topography top
     
    37163753       CALL cpu_log( log_point_s(56), 'accretion', 'start' )
    37173754
    3718        DO  i = nxlg, nxrg
    3719           DO  j = nysg, nyng
     3755       DO  i = nxl, nxr
     3756          DO  j = nys, nyn
    37203757             DO  k = nzb+1, nzt
    37213758!
     
    38773914       CALL cpu_log( log_point_s(57), 'selfcollection', 'start' )
    38783915
    3879        DO  i = nxlg, nxrg
    3880           DO  j = nysg, nyng
     3916       DO  i = nxl, nxr
     3917          DO  j = nys, nyn
    38813918             DO  k = nzb+1, nzt
    38823919!
     
    39944031       CALL cpu_log( log_point_s(58), 'evaporation', 'start' )
    39954032
    3996        DO  i = nxlg, nxrg
    3997           DO  j = nysg, nyng
     4033       DO  i = nxl, nxr
     4034          DO  j = nys, nyn
    39984035             DO  k = nzb+1, nzt
    39994036!
     
    42304267       sed_nc(nzt+1) = 0.0_wp
    42314268
    4232        DO  i = nxlg, nxrg
    4233           DO  j = nysg, nyng
     4269       DO  i = nxl, nxr
     4270          DO  j = nys, nyn
    42344271             DO  k = nzt, nzb+1, -1
    42354272!
     
    44304467!
    44314468!--    Compute velocities
    4432        DO  i = nxlg, nxrg
    4433           DO  j = nysg, nyng
     4469       DO  i = nxl, nxr
     4470          DO  j = nys, nyn
    44344471             DO  k = nzb+1, nzt
    44354472!
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3886 r3887  
    522522       MODULE PROCEDURE chem_non_transport_physics_ij
    523523    END INTERFACE chem_non_transport_physics
     524   
     525    INTERFACE chem_exchange_horiz
     526       MODULE PROCEDURE chem_exchange_horiz
     527    END INTERFACE chem_exchange_horiz   
    524528
    525529    INTERFACE chem_prognostic_equations
     
    622626         chem_actions, chem_prognostic_equations, chem_rrd_local,             &
    623627         chem_statistics, chem_swap_timelevel, chem_wrd_local, chem_depo,     &
    624          chem_non_transport_physics
     628         chem_non_transport_physics, chem_exchange_horiz
    625629
    626630 CONTAINS
     
    915919    DO  lsp = 1, nspec
    916920
    917        CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
     921       CALL exchange_horiz( chem_species(lsp)%conc, nbgp )
    918922       lsp_usr = 1
    919923       DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     
    24602464
    24612465 END SUBROUTINE chem_non_transport_physics_ij
     2466 
     2467 SUBROUTINE chem_exchange_horiz
     2468
     2469
     2470    INTEGER(iwp) ::  i  !< grid index in x-direction
     2471    INTEGER(iwp) ::  j  !< grid index in y-direction
     2472
     2473    i = i + j
     2474! !
     2475! !-- Loop over chemical species       
     2476!     CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' )
     2477!     DO  lsp = 1, nspec
     2478!        CALL exchange_horiz( chem_species(lsp)%conc, nbgp )   
     2479!        lsp_usr = 1 
     2480!        DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
     2481!           IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) )  THEN
     2482!           
     2483!              CALL chem_boundary_conds( chem_species(lsp)%conc_p,               &
     2484!                                        chem_species(lsp)%conc_pr_init )
     2485!             
     2486!           ENDIF
     2487!           lsp_usr = lsp_usr +1
     2488!        ENDDO
     2489!
     2490!
     2491!     ENDDO
     2492!     CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' )
     2493
     2494
     2495 END SUBROUTINE chem_exchange_horiz
     2496
    24622497
    24632498 
  • palm/trunk/SOURCE/module_interface.f90

    r3885 r3887  
    152152               bcm_actions,                                                    &
    153153               bcm_non_transport_physics,                                      &
     154               bcm_exchange_horiz,                                             &               
    154155               bcm_prognostic_equations,                                       &
    155156               bcm_swap_timelevel,                                             &
     
    179180              chem_statistics,                                                 &
    180181              chem_rrd_local,                                                  &
    181                chem_wrd_local
     182              chem_wrd_local
    182183
    183184    USE flight_mod,                                                            &
     
    392393       module_interface_actions,                                               &
    393394       module_interface_non_transport_physics,                                 &
     395       module_interface_exchange_horiz,                                        &
    394396       module_interface_prognostic_equations,                                  &
    395397       module_interface_swap_timelevel,                                        &
     
    458460       MODULE PROCEDURE module_interface_non_transport_physics_ij
    459461    END INTERFACE module_interface_non_transport_physics
    460 
     462   
     463    INTERFACE module_interface_exchange_horiz
     464       MODULE PROCEDURE module_interface_exchange_horiz
     465    END INTERFACE module_interface_exchange_horiz
     466   
    461467    INTERFACE module_interface_prognostic_equations
    462468       MODULE PROCEDURE module_interface_prognostic_equations
     
    972978
    973979 END SUBROUTINE module_interface_non_transport_physics_ij
     980 
     981!------------------------------------------------------------------------------!
     982! Description:
     983! ------------
     984!> Exchange horiz for module-specific quantities
     985!------------------------------------------------------------------------------!
     986 SUBROUTINE module_interface_exchange_horiz()
     987
     988
     989    IF ( bulk_cloud_model    )  CALL bcm_exchange_horiz()
     990
     991
     992 END SUBROUTINE module_interface_exchange_horiz
    974993
    975994
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3885 r3887  
    2525! -----------------
    2626! $Id$
     27! Implicit Bugfix for chemistry model, loop for non_transport_physics over
     28! ghost points is avoided. Instead introducing module_interface_exchange_horiz.
     29!
     30! 3885 2019-04-11 11:29:34Z kanani
    2731! Changes related to global restructuring of location messages and introduction
    2832! of additional debug messages
     
    441445        ONLY:  module_interface_actions, &
    442446               module_interface_non_transport_physics, &
     447               module_interface_exchange_horiz, &
    443448               module_interface_prognostic_equations
    444449
     
    533538    !$OMP PARALLEL PRIVATE (i,j)
    534539    !$OMP DO
    535     DO  i = nxlg, nxrg
    536        DO  j = nysg, nyng
     540    DO  i = nxl, nxr
     541       DO  j = nys, nyn
    537542!
    538543!--       Calculate non transport physics for all other modules
     
    540545       ENDDO
    541546    ENDDO
     547!
     548!-- Module Inferface for exchange horiz after non_transport_physics but before
     549!-- advection. Therefore, non_transport_physics must not run for ghost points.
     550    CALL module_interface_exchange_horiz()
    542551    !$OMP END PARALLEL
    543552
     
    12101219!-- Calculate non transport physics for all other modules
    12111220    CALL module_interface_non_transport_physics
    1212 
     1221!
     1222!-- Module Inferface for exchange horiz after non_transport_physics but before
     1223!-- advection. Therefore, non_transport_physics must not run for ghost points.     
     1224    CALL module_interface_exchange_horiz()
     1225   
    12131226!
    12141227!-- u-velocity component
Note: See TracChangeset for help on using the changeset viewer.