Changeset 3878


Ignore:
Timestamp:
Apr 8, 2019 7:35:54 PM (5 years ago)
Author:
knoop
Message:

Added chem_non_transport_physics module interface to chemistry_model_mod and moved respective calls into it

Location:
palm/trunk/SOURCE
Files:
3 edited

Legend:

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

    r3877 r3878  
    314314        ONLY:  photolysis_control
    315315
     316    USE cpulog,                                                                                    &
     317        ONLY:  cpu_log, log_point_s
     318
    316319    USE statistics
    317320
     
    486489    END INTERFACE chem_actions
    487490
     491    INTERFACE chem_non_transport_physics
     492       MODULE PROCEDURE chem_non_transport_physics
     493       MODULE PROCEDURE chem_non_transport_physics_ij
     494    END INTERFACE chem_non_transport_physics
     495
    488496    INTERFACE chem_prognostic_equations
    489497       MODULE PROCEDURE chem_prognostic_equations
     
    583591         chem_init_profiles, chem_integrate, chem_parin,                      &
    584592         chem_actions, chem_prognostic_equations, chem_rrd_local,             &
    585          chem_statistics, chem_swap_timelevel, chem_wrd_local, chem_depo
     593         chem_statistics, chem_swap_timelevel, chem_wrd_local, chem_depo,     &
     594         chem_non_transport_physics
    586595
    587596 CONTAINS
     
    23492358
    23502359    END SUBROUTINE chem_actions_ij
     2360
     2361
     2362!------------------------------------------------------------------------------!
     2363! Description:
     2364! ------------
     2365!> Call for all grid points
     2366!------------------------------------------------------------------------------!
     2367 SUBROUTINE chem_non_transport_physics()
     2368
     2369
     2370    INTEGER(iwp) ::  i  !<
     2371    INTEGER(iwp) ::  j  !<
     2372
     2373!
     2374!-- Calculation of chemical reactions and deposition.
     2375    IF ( chem_gasphase_on ) THEN
     2376
     2377       IF ( intermediate_timestep_count == 1 .OR. call_chem_at_all_substeps )  THEN
     2378
     2379          CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' )
     2380          !$OMP PARALLEL PRIVATE (i,j)
     2381          !$OMP DO schedule(static,1)
     2382          DO  i = nxl, nxr
     2383             DO  j = nys, nyn
     2384                CALL chem_integrate( i, j )
     2385             ENDDO
     2386          ENDDO
     2387          !$OMP END PARALLEL
     2388          CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
     2389
     2390          IF ( deposition_dry )  THEN
     2391             CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
     2392             DO  i = nxl, nxr
     2393                DO  j = nys, nyn
     2394                   CALL chem_depo( i, j )
     2395                ENDDO
     2396             ENDDO
     2397             CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
     2398          ENDIF
     2399
     2400       ENDIF
     2401
     2402    ENDIF
     2403
     2404 END SUBROUTINE chem_non_transport_physics
     2405
     2406
     2407!------------------------------------------------------------------------------!
     2408! Description:
     2409! ------------
     2410!> Call for grid points i,j
     2411!------------------------------------------------------------------------------!
     2412
     2413 SUBROUTINE chem_non_transport_physics_ij( i, j )
     2414
     2415
     2416    INTEGER(iwp), INTENT(IN) ::  i  !< grid index in x-direction
     2417    INTEGER(iwp), INTENT(IN) ::  j  !< grid index in y-direction
     2418
     2419!
     2420!-- Calculation of chemical reactions and deposition.
     2421    IF ( chem_gasphase_on ) THEN
     2422
     2423       IF ( intermediate_timestep_count == 1 .OR. call_chem_at_all_substeps )  THEN
     2424
     2425          CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' )
     2426          CALL chem_integrate( i, j )
     2427          CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
     2428
     2429          IF ( deposition_dry )  THEN
     2430             CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
     2431             CALL chem_depo( i, j )
     2432             CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
     2433          ENDIF
     2434
     2435       ENDIF
     2436
     2437    ENDIF
     2438
     2439 END SUBROUTINE chem_non_transport_physics_ij
    23512440
    23522441 
  • palm/trunk/SOURCE/module_interface.f90

    r3877 r3878  
    167167              chem_header,                                                     &
    168168              chem_actions,                                                    &
     169              chem_non_transport_physics,                                      &
    169170              chem_swap_timelevel,                                             &
    170171              chem_3d_data_averaging,                                          &
     
    935936
    936937    IF ( bulk_cloud_model    )  CALL bcm_non_transport_physics()
     938    IF ( air_chemistry       )  CALL chem_non_transport_physics()
    937939
    938940
     
    952954
    953955
     956    IF ( air_chemistry       )  CALL chem_non_transport_physics( i, j )
    954957    IF ( bulk_cloud_model    )  CALL bcm_non_transport_physics( i, j )
    955958
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3877 r3878  
    395395
    396396    USE chemistry_model_mod,                                                   &
    397         ONLY:  chem_boundary_conds, chem_depo, chem_integrate,                 &
    398                chem_prognostic_equations
     397        ONLY:  chem_boundary_conds, chem_prognostic_equations
    399398
    400399    USE control_parameters,                                                    &
     
    528527    CALL cpu_log( log_point(32), 'all progn.equations', 'start' )
    529528
    530 !
    531 !-- Calculation of chemical reactions. This is done outside of main loop,
    532 !-- since exchange of ghost points is required after this update of the
    533 !-- concentrations of chemical species                                   
     529    !$OMP PARALLEL PRIVATE (i,j)
     530    !$OMP DO
     531    DO  i = nxlg, nxrg
     532       DO  j = nysg, nyng
     533!
     534!--       Calculate non transport physics for all other modules
     535          CALL module_interface_non_transport_physics( i, j )
     536       ENDDO
     537    ENDDO
     538    !$OMP END PARALLEL
     539
    534540    IF ( air_chemistry )  THEN
    535 !
    536 !--    Chemical reactions and deposition
    537        IF ( chem_gasphase_on ) THEN
    538 
    539           IF ( intermediate_timestep_count == 1 .OR.                        &
    540              call_chem_at_all_substeps )  THEN
    541 
    542              CALL cpu_log( log_point_s(19), 'chem.reactions', 'start' )
    543              !$OMP PARALLEL PRIVATE (i,j)
    544              !$OMP DO schedule(static,1)
    545              DO  i = nxl, nxr
    546                 DO  j = nys, nyn
    547                    CALL chem_integrate (i,j)
    548                 ENDDO
    549              ENDDO
    550              !$OMP END PARALLEL
    551              CALL cpu_log( log_point_s(19), 'chem.reactions', 'stop' )
    552 
    553              IF ( deposition_dry )  THEN
    554                 CALL cpu_log( log_point_s(24), 'chem.deposition', 'start' )
    555                 DO  i = nxl, nxr
    556                    DO  j = nys, nyn
    557                       CALL chem_depo(i,j)
    558                    ENDDO
    559                 ENDDO
    560                 CALL cpu_log( log_point_s(24), 'chem.deposition', 'stop' )
    561              ENDIF
    562           ENDIF
    563        ENDIF
    564541!
    565542!--    Loop over chemical species       
     
    639616
    640617    ENDIF
    641 
    642     !$OMP PARALLEL PRIVATE (i,j)
    643     !$OMP DO
    644     DO  i = nxlg, nxrg
    645        DO  j = nysg, nyng
    646 !
    647 !--       Calculate non transport physics for all other modules
    648           CALL module_interface_non_transport_physics( i, j )
    649        ENDDO
    650     ENDDO
    651     !$OMP END PARALLEL
    652618
    653619!
Note: See TracChangeset for help on using the changeset viewer.