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

File:
1 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 
Note: See TracChangeset for help on using the changeset viewer.