Changeset 3880


Ignore:
Timestamp:
Apr 8, 2019 9:43:02 PM (5 years ago)
Author:
knoop
Message:

Moved chem_prognostic_equations into module_interface

Location:
palm/trunk/SOURCE
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r3877 r3880  
    15131513        buoyancy.o \
    15141514        chemistry_model_mod.o \
    1515         chem_gasphase_mod.o \
    1516         chem_modules.o \
    1517         chem_photolysis_mod.o \
    15181515        coriolis.o \
    15191516        cpulog_mod.o \
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3879 r3880  
    285285 MODULE chemistry_model_mod
    286286
     287    USE advec_s_pw_mod,                                                                            &
     288         ONLY:  advec_s_pw
     289
     290    USE advec_s_up_mod,                                                                            &
     291         ONLY:  advec_s_up
     292
     293    USE advec_ws,                                                                                  &
     294         ONLY:  advec_s_ws
     295
     296    USE diffusion_s_mod,                                                                           &
     297         ONLY:  diffusion_s
     298
    287299    USE kinds,                                                                                     &
    288300         ONLY:  iwp, wp
    289301
    290302    USE indices,                                                                                   &
    291          ONLY:  nbgp, nz, nzb, nzt, nysg, nyng, nxlg, nxrg, nys, nyn, nx, nxl, nxr, ny, wall_flags_0
     303         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, ny, nyn, nyng, nys, nysg, nz, nzb, nzt, wall_flags_0
    292304
    293305    USE pegrid,                                                                                    &
     
    319331    USE statistics
    320332
     333    USE surface_mod,                                                                               &
     334         ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
     335
    321336    IMPLICIT NONE
     337
    322338    PRIVATE
    323339    SAVE
     
    614630 SUBROUTINE chem_3d_data_averaging( mode, variable )
    615631
     632
    616633    USE control_parameters
    617 
    618     USE indices
    619 
    620     USE kinds
    621 
    622     USE surface_mod,                                                         &
    623          ONLY:  surf_def_h, surf_lsm_h, surf_usm_h   
    624 
    625     IMPLICIT NONE
    626634
    627635    CHARACTER (LEN=*) ::  mode     !<
     
    736744        ONLY:  bc_radiation_l, bc_radiation_n, bc_radiation_r, bc_radiation_s
    737745
    738     USE indices,                                                               & 
    739         ONLY:  nxl, nxr, nzt                             
    740 
    741746    USE arrays_3d,                                                             &     
    742747        ONLY:  dzu                                               
     
    873878! ------------
    874879!> Boundary conditions for prognostic variables in chemistry: decycling in the
    875 !> x-direction
     880!> x-direction-
     881!> Decycling of chemistry variables: Dirichlet BCs with cyclic is frequently not
     882!> approproate for chemicals compounds since they may accumulate too much.
     883!> If no proper boundary conditions from a DYNAMIC input file are available,
     884!> de-cycling applies the initial profiles at the inflow boundaries for
     885!> Dirichlet boundary conditions
    876886!------------------------------------------------------------------------------!
    877887 SUBROUTINE chem_boundary_conds_decycle()
    878 !
    879 !-- Decycling of chemistry variables: Dirichlet BCs with cyclic is frequently not
    880 !-- approproate for chemicals compounds since they may accumulate too much.
    881 !-- If no proper boundary conditions from a DYNAMIC input file are available,
    882 !-- de-cycling applies the initial profiles at the inflow boundaries for
    883 !-- Dirichlet boundary conditions
    884 
    885     IMPLICIT NONE
     888
     889
    886890    INTEGER(iwp) ::  boundary  !<
    887891    INTEGER(iwp) ::  ee        !<
     
    10601064 SUBROUTINE chem_check_data_output( var, unit, i, ilen, k )
    10611065
    1062     IMPLICIT NONE
    10631066
    10641067    CHARACTER (LEN=*) ::  unit     !<
     
    11291132
    11301133    USE arrays_3d
     1134
    11311135    USE control_parameters,                                                    &
    11321136        ONLY:  data_output_pr, message_string
    1133     USE indices
     1137
    11341138    USE profil_parameter
     1139
    11351140    USE statistics
    11361141
    1137 
    1138     IMPLICIT NONE
    11391142
    11401143    CHARACTER (LEN=*) ::  unit     !<
     
    11801183 SUBROUTINE chem_check_parameters
    11811184
    1182     IMPLICIT NONE
    11831185
    11841186    LOGICAL  ::  found
     
    12801282                                  two_d, nzb_do, nzt_do, fill_value )
    12811283
    1282     USE indices
    1283 
    1284     USE kinds
    1285 
    1286     IMPLICIT NONE
    12871284
    12881285    CHARACTER (LEN=*) ::  grid       !<
     
    13641361 SUBROUTINE chem_data_output_3d( av, variable, found, local_pf, fill_value, nzb_do, nzt_do )
    13651362
    1366     USE indices
    1367 
    1368     USE kinds
    13691363
    13701364    USE surface_mod
    1371 
    1372 
    1373     IMPLICIT NONE
    13741365
    13751366    CHARACTER (LEN=*)    ::  variable     !<
     
    14781469 SUBROUTINE chem_data_output_mask( av, variable, found, local_pf )
    14791470
     1471
    14801472    USE control_parameters
    1481     USE indices
    1482     USE kinds
     1473
    14831474    USE surface_mod,                                                                  &
    14841475        ONLY:  get_topography_top_index_ji
    14851476
    1486     IMPLICIT NONE
    14871477
    14881478    CHARACTER(LEN=5)  ::  grid        !< flag to distinquish between staggered grids
     
    16071597 SUBROUTINE chem_define_netcdf_grid( var, found, grid_x, grid_y, grid_z )
    16081598
    1609     IMPLICIT NONE
    16101599
    16111600    CHARACTER (LEN=*), INTENT(IN)  ::  var          !<
     
    16391628 SUBROUTINE chem_header( io )
    16401629
    1641     IMPLICIT NONE
    16421630
    16431631    INTEGER(iwp), INTENT(IN) ::  io            !< Unit of the output file
     
    17631751        ONLY:  init_3d
    17641752
    1765     IMPLICIT NONE
    17661753
    17671754    INTEGER(iwp) ::  i !< running index x dimension
     
    18091796               netcdf_data_input_chemistry_data
    18101797
    1811     IMPLICIT NONE
    18121798!
    18131799!-- Local variables
     
    19701956    USE chem_modules
    19711957
    1972     IMPLICIT NONE
    19731958!
    19741959!-- Local variables
     
    20532038        ONLY:  dt_3d, intermediate_timestep_count, time_since_reference_point
    20542039
    2055     IMPLICIT NONE
    20562040
    20572041    INTEGER,INTENT(IN)       :: i
     
    21632147    USE control_parameters
    21642148
    2165     USE kinds
    21662149    USE pegrid
    21672150    USE statistics
    21682151
    2169     IMPLICIT NONE
    21702152
    21712153    CHARACTER (LEN=80) ::  line                        !< dummy string that contains the current line of the parameter file
     
    24772459!> prognostic_equations.
    24782460!------------------------------------------------------------------------------!
    2479  SUBROUTINE chem_prognostic_equations( cs_scalar_p, cs_scalar, tcs_scalar_m,   &
    2480       pr_init_cs, ilsp )
    2481 
    2482     USE advec_s_pw_mod,                                                        &
    2483          ONLY:  advec_s_pw
    2484     USE advec_s_up_mod,                                                        &
    2485          ONLY:  advec_s_up
    2486     USE advec_ws,                                                              &
    2487          ONLY:  advec_s_ws
    2488     USE diffusion_s_mod,                                                       &
    2489          ONLY:  diffusion_s
    2490     USE indices,                                                               &
    2491          ONLY:  nxl, nxr, nyn, nys, wall_flags_0
    2492     USE pegrid
    2493     USE surface_mod,                                                           &
    2494          ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h,     &
    2495          surf_usm_v
    2496 
    2497     IMPLICIT NONE
     2461 SUBROUTINE chem_prognostic_equations()
     2462
    24982463
    24992464    INTEGER ::  i   !< running index
     
    25012466    INTEGER ::  k   !< running index
    25022467
    2503     INTEGER(iwp),INTENT(IN) ::  ilsp          !<
    2504 
    2505     REAL(wp), DIMENSION(0:nz+1) ::  pr_init_cs   !<
    2506 
    2507     REAL(wp), DIMENSION(:,:,:), POINTER ::  cs_scalar      !<
    2508     REAL(wp), DIMENSION(:,:,:), POINTER ::  cs_scalar_p    !<
    2509     REAL(wp), DIMENSION(:,:,:), POINTER ::  tcs_scalar_m   !<
    2510 
    2511 
    2512 !
    2513 !-- Tendency terms for chemical species
    2514     tend = 0.0_wp
    2515 !   
    2516 !-- Advection terms
    2517     IF ( timestep_scheme(1:5) == 'runge' )  THEN
    2518        IF ( ws_scheme_sca )  THEN
    2519           CALL advec_s_ws( cs_scalar, 'kc' )
     2468    INTEGER(iwp) ::  ilsp   !<
     2469
     2470
     2471    CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'start' )
     2472
     2473    DO  ilsp = 1, nspec
     2474!
     2475!--    Tendency terms for chemical species
     2476       tend = 0.0_wp
     2477!
     2478!--    Advection terms
     2479       IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2480          IF ( ws_scheme_sca )  THEN
     2481             CALL advec_s_ws( chem_species(ilsp)%conc, 'kc' )
     2482          ELSE
     2483             CALL advec_s_pw( chem_species(ilsp)%conc )
     2484          ENDIF
    25202485       ELSE
    2521           CALL advec_s_pw( cs_scalar )
     2486          CALL advec_s_up( chem_species(ilsp)%conc )
    25222487       ENDIF
    2523     ELSE
    2524        CALL advec_s_up( cs_scalar )
    2525     ENDIF
    2526 !
    2527 !-- Diffusion terms  (the last three arguments are zero)
    2528     CALL diffusion_s( cs_scalar,                                               &
    2529          surf_def_h(0)%cssws(ilsp,:),                             &
    2530          surf_def_h(1)%cssws(ilsp,:),                             &
    2531          surf_def_h(2)%cssws(ilsp,:),                             &
    2532          surf_lsm_h%cssws(ilsp,:),                                &
    2533          surf_usm_h%cssws(ilsp,:),                                &
    2534          surf_def_v(0)%cssws(ilsp,:),                             &
    2535          surf_def_v(1)%cssws(ilsp,:),                             &
    2536          surf_def_v(2)%cssws(ilsp,:),                             &
    2537          surf_def_v(3)%cssws(ilsp,:),                             &
    2538          surf_lsm_v(0)%cssws(ilsp,:),                             &
    2539          surf_lsm_v(1)%cssws(ilsp,:),                             &
    2540          surf_lsm_v(2)%cssws(ilsp,:),                             &
    2541          surf_lsm_v(3)%cssws(ilsp,:),                             &
    2542          surf_usm_v(0)%cssws(ilsp,:),                             &
    2543          surf_usm_v(1)%cssws(ilsp,:),                             &
    2544          surf_usm_v(2)%cssws(ilsp,:),                             &
    2545          surf_usm_v(3)%cssws(ilsp,:) )
    2546 !   
    2547 !-- Prognostic equation for chemical species
    2548     DO  i = nxl, nxr
    2549        DO  j = nys, nyn   
    2550           DO  k = nzb+1, nzt
    2551              cs_scalar_p(k,j,i) =   cs_scalar(k,j,i)                           &
    2552                   + ( dt_3d  *                                 &
    2553                   (   tsc(2) * tend(k,j,i)                 &
    2554                   + tsc(3) * tcs_scalar_m(k,j,i)         &
    2555                   )                                        &
    2556                   - tsc(5) * rdf_sc(k)                       &
    2557                   * ( cs_scalar(k,j,i) - pr_init_cs(k) )    &   
    2558                   )                                          &
    2559                   * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )       
    2560 
    2561              IF ( cs_scalar_p(k,j,i) < 0.0_wp )  cs_scalar_p(k,j,i) = 0.1_wp * cs_scalar(k,j,i)
     2488!
     2489!--    Diffusion terms  (the last three arguments are zero)
     2490       CALL diffusion_s( chem_species(ilsp)%conc,                                                  &
     2491            surf_def_h(0)%cssws(ilsp,:),                                                           &
     2492            surf_def_h(1)%cssws(ilsp,:),                                                           &
     2493            surf_def_h(2)%cssws(ilsp,:),                                                           &
     2494            surf_lsm_h%cssws(ilsp,:),                                                              &
     2495            surf_usm_h%cssws(ilsp,:),                                                              &
     2496            surf_def_v(0)%cssws(ilsp,:),                                                           &
     2497            surf_def_v(1)%cssws(ilsp,:),                                                           &
     2498            surf_def_v(2)%cssws(ilsp,:),                                                           &
     2499            surf_def_v(3)%cssws(ilsp,:),                                                           &
     2500            surf_lsm_v(0)%cssws(ilsp,:),                                                           &
     2501            surf_lsm_v(1)%cssws(ilsp,:),                                                           &
     2502            surf_lsm_v(2)%cssws(ilsp,:),                                                           &
     2503            surf_lsm_v(3)%cssws(ilsp,:),                                                           &
     2504            surf_usm_v(0)%cssws(ilsp,:),                                                           &
     2505            surf_usm_v(1)%cssws(ilsp,:),                                                           &
     2506            surf_usm_v(2)%cssws(ilsp,:),                                                           &
     2507            surf_usm_v(3)%cssws(ilsp,:) )
     2508!
     2509!--    Prognostic equation for chemical species
     2510       DO  i = nxl, nxr
     2511          DO  j = nys, nyn
     2512             DO  k = nzb+1, nzt
     2513                chem_species(ilsp)%conc_p(k,j,i) =   chem_species(ilsp)%conc(k,j,i)                &
     2514                     + ( dt_3d  *                                                                  &
     2515                     (   tsc(2) * tend(k,j,i)                                                      &
     2516                     + tsc(3) * chem_species(ilsp)%tconc_m(k,j,i)                                  &
     2517                     )                                                                             &
     2518                     - tsc(5) * rdf_sc(k)                                                          &
     2519                     * ( chem_species(ilsp)%conc(k,j,i) - chem_species(ilsp)%conc_pr_init(k) )     &
     2520                     )                                                                             &
     2521                     * MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_0(k,j,i), 0 ) )
     2522
     2523                IF ( chem_species(ilsp)%conc_p(k,j,i) < 0.0_wp )  THEN
     2524                   chem_species(ilsp)%conc_p(k,j,i) = 0.1_wp * chem_species(ilsp)%conc(k,j,i)
     2525                ENDIF
     2526             ENDDO
    25622527          ENDDO
    25632528       ENDDO
    2564     ENDDO
    2565 !
    2566 !-- Calculate tendencies for the next Runge-Kutta step
    2567     IF ( timestep_scheme(1:5) == 'runge' )  THEN
    2568        IF ( intermediate_timestep_count == 1 )  THEN
    2569           DO  i = nxl, nxr
    2570              DO  j = nys, nyn   
    2571                 DO  k = nzb+1, nzt
    2572                    tcs_scalar_m(k,j,i) = tend(k,j,i)
     2529!
     2530!--    Calculate tendencies for the next Runge-Kutta step
     2531       IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2532          IF ( intermediate_timestep_count == 1 )  THEN
     2533             DO  i = nxl, nxr
     2534                DO  j = nys, nyn
     2535                   DO  k = nzb+1, nzt
     2536                      chem_species(ilsp)%tconc_m(k,j,i) = tend(k,j,i)
     2537                   ENDDO
    25732538                ENDDO
    25742539             ENDDO
    2575           ENDDO
    2576        ELSEIF ( intermediate_timestep_count < &
    2577             intermediate_timestep_count_max )  THEN
    2578           DO  i = nxl, nxr
    2579              DO  j = nys, nyn
    2580                 DO  k = nzb+1, nzt
    2581                    tcs_scalar_m(k,j,i) = - 9.5625_wp * tend(k,j,i)             &
    2582                         + 5.3125_wp * tcs_scalar_m(k,j,i)
     2540          ELSEIF ( intermediate_timestep_count < &
     2541               intermediate_timestep_count_max )  THEN
     2542             DO  i = nxl, nxr
     2543                DO  j = nys, nyn
     2544                   DO  k = nzb+1, nzt
     2545                      chem_species(ilsp)%tconc_m(k,j,i) = - 9.5625_wp * tend(k,j,i)                &
     2546                           + 5.3125_wp * chem_species(ilsp)%tconc_m(k,j,i)
     2547                   ENDDO
    25832548                ENDDO
    25842549             ENDDO
    2585           ENDDO
     2550          ENDIF
    25862551       ENDIF
    2587     ENDIF
     2552
     2553    ENDDO
     2554
     2555    CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'stop' )
    25882556
    25892557 END SUBROUTINE chem_prognostic_equations
     
    25982566!> prognostic_equations.
    25992567!------------------------------------------------------------------------------!
    2600  SUBROUTINE chem_prognostic_equations_ij( cs_scalar_p, cs_scalar, tcs_scalar_m,                 &
    2601       pr_init_cs, i, j, i_omp_start, tn, ilsp, flux_s_cs, diss_s_cs,                            &
    2602       flux_l_cs, diss_l_cs )
    2603     USE pegrid         
    2604     USE advec_ws,                                                                               &
    2605          ONLY:  advec_s_ws
    2606     USE advec_s_pw_mod,                                                                         &
    2607          ONLY:  advec_s_pw
    2608     USE advec_s_up_mod,                                                                         &
    2609          ONLY:  advec_s_up
    2610     USE diffusion_s_mod,                                                                        &
    2611          ONLY:  diffusion_s
    2612     USE indices,                                                                                &
    2613          ONLY:  wall_flags_0
    2614     USE surface_mod,                                                                            &
    2615          ONLY:  surf_def_h, surf_def_v, surf_lsm_h, surf_lsm_v, surf_usm_h, surf_usm_v
    2616 
    2617 
    2618     IMPLICIT NONE
    2619 
    2620     REAL(wp), DIMENSION(:,:,:), POINTER   :: cs_scalar_p, cs_scalar, tcs_scalar_m
    2621 
    2622     INTEGER(iwp),INTENT(IN) :: i, j, i_omp_start, tn, ilsp
    2623     REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1)          :: flux_s_cs   !<
    2624     REAL(wp), DIMENSION(nzb+1:nzt,0:threads_per_task-1)          :: diss_s_cs   !<
    2625     REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1)  :: flux_l_cs   !<
    2626     REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn,0:threads_per_task-1)  :: diss_l_cs   !<
    2627     REAL(wp), DIMENSION(0:nz+1)                                  :: pr_init_cs  !<
    2628 
     2568 SUBROUTINE chem_prognostic_equations_ij( i, j, i_omp_start, tn )
     2569
     2570
     2571    INTEGER(iwp),INTENT(IN) :: i, j, i_omp_start, tn
     2572    INTEGER(iwp) :: ilsp
    26292573!
    26302574!-- local variables
    26312575
    26322576    INTEGER :: k
     2577
     2578    DO  ilsp = 1, nspec
    26332579!
    26342580!--    Tendency-terms for chem spcs.
    2635     tend(:,j,i) = 0.0_wp
    2636 !   
    2637 !-- Advection terms
    2638     IF ( timestep_scheme(1:5) == 'runge' )  THEN
    2639        IF ( ws_scheme_sca )  THEN
    2640           CALL advec_s_ws( i, j, cs_scalar, 'kc', flux_s_cs, diss_s_cs,                &
    2641                flux_l_cs, diss_l_cs, i_omp_start, tn )
     2581       tend(:,j,i) = 0.0_wp
     2582!
     2583!--    Advection terms
     2584       IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2585          IF ( ws_scheme_sca )  THEN
     2586             CALL advec_s_ws( i, j, chem_species(ilsp)%conc, 'kc', chem_species(ilsp)%flux_s_cs,   &
     2587                              chem_species(ilsp)%diss_s_cs, chem_species(ilsp)%flux_l_cs,          &
     2588                              chem_species(ilsp)%diss_l_cs, i_omp_start, tn )
     2589          ELSE
     2590             CALL advec_s_pw( i, j, chem_species(ilsp)%conc )
     2591          ENDIF
    26422592       ELSE
    2643           CALL advec_s_pw( i, j, cs_scalar )
     2593          CALL advec_s_up( i, j, chem_species(ilsp)%conc )
    26442594       ENDIF
    2645     ELSE
    2646        CALL advec_s_up( i, j, cs_scalar )
    2647     ENDIF
    2648 !
    2649 !-- Diffusion terms (the last three arguments are zero)
    2650 
    2651     CALL diffusion_s( i, j, cs_scalar,                                                 &
    2652          surf_def_h(0)%cssws(ilsp,:), surf_def_h(1)%cssws(ilsp,:),        &
    2653          surf_def_h(2)%cssws(ilsp,:),                                     &
    2654          surf_lsm_h%cssws(ilsp,:), surf_usm_h%cssws(ilsp,:),              &
    2655          surf_def_v(0)%cssws(ilsp,:), surf_def_v(1)%cssws(ilsp,:),        &
    2656          surf_def_v(2)%cssws(ilsp,:), surf_def_v(3)%cssws(ilsp,:),        &
    2657          surf_lsm_v(0)%cssws(ilsp,:), surf_lsm_v(1)%cssws(ilsp,:),        &
    2658          surf_lsm_v(2)%cssws(ilsp,:), surf_lsm_v(3)%cssws(ilsp,:),        &
    2659          surf_usm_v(0)%cssws(ilsp,:), surf_usm_v(1)%cssws(ilsp,:),        &
    2660          surf_usm_v(2)%cssws(ilsp,:), surf_usm_v(3)%cssws(ilsp,:) )
    2661 !   
    2662 !-- Prognostic equation for chem spcs
    2663     DO  k = nzb+1, nzt
    2664        cs_scalar_p(k,j,i) = cs_scalar(k,j,i) + ( dt_3d  *                       &
    2665             ( tsc(2) * tend(k,j,i) +         &
    2666             tsc(3) * tcs_scalar_m(k,j,i) ) &
    2667             - tsc(5) * rdf_sc(k)             &
    2668             * ( cs_scalar(k,j,i) - pr_init_cs(k) )    &   
    2669             )                                                  &
    2670             * MERGE( 1.0_wp, 0.0_wp,                  &     
    2671             BTEST( wall_flags_0(k,j,i), 0 )   &             
    2672             )       
    2673 
    2674        IF ( cs_scalar_p(k,j,i) < 0.0_wp )  cs_scalar_p(k,j,i) = 0.1_wp * cs_scalar(k,j,i)    !FKS6
     2595!
     2596!--    Diffusion terms (the last three arguments are zero)
     2597
     2598       CALL diffusion_s( i, j, chem_species(ilsp)%conc,                                            &
     2599            surf_def_h(0)%cssws(ilsp,:), surf_def_h(1)%cssws(ilsp,:),                              &
     2600            surf_def_h(2)%cssws(ilsp,:),                                                           &
     2601            surf_lsm_h%cssws(ilsp,:), surf_usm_h%cssws(ilsp,:),                                    &
     2602            surf_def_v(0)%cssws(ilsp,:), surf_def_v(1)%cssws(ilsp,:),                              &
     2603            surf_def_v(2)%cssws(ilsp,:), surf_def_v(3)%cssws(ilsp,:),                              &
     2604            surf_lsm_v(0)%cssws(ilsp,:), surf_lsm_v(1)%cssws(ilsp,:),                              &
     2605            surf_lsm_v(2)%cssws(ilsp,:), surf_lsm_v(3)%cssws(ilsp,:),                              &
     2606            surf_usm_v(0)%cssws(ilsp,:), surf_usm_v(1)%cssws(ilsp,:),                              &
     2607            surf_usm_v(2)%cssws(ilsp,:), surf_usm_v(3)%cssws(ilsp,:) )
     2608!
     2609!--    Prognostic equation for chem spcs
     2610       DO  k = nzb+1, nzt
     2611          chem_species(ilsp)%conc_p(k,j,i) = chem_species(ilsp)%conc(k,j,i) + ( dt_3d  *           &
     2612               ( tsc(2) * tend(k,j,i) +                                                            &
     2613               tsc(3) * chem_species(ilsp)%tconc_m(k,j,i) )                                        &
     2614               - tsc(5) * rdf_sc(k)                                                                &
     2615               * ( chem_species(ilsp)%conc(k,j,i) - chem_species(ilsp)%conc_pr_init(k) )           &
     2616               )                                                                                   &
     2617               * MERGE( 1.0_wp, 0.0_wp,                                                            &
     2618               BTEST( wall_flags_0(k,j,i), 0 )                                                     &
     2619               )
     2620
     2621          IF ( chem_species(ilsp)%conc_p(k,j,i) < 0.0_wp )  THEN
     2622             chem_species(ilsp)%conc_p(k,j,i) = 0.1_wp * chem_species(ilsp)%conc(k,j,i)    !FKS6
     2623          ENDIF
     2624       ENDDO
     2625!
     2626!--    Calculate tendencies for the next Runge-Kutta step
     2627       IF ( timestep_scheme(1:5) == 'runge' )  THEN
     2628          IF ( intermediate_timestep_count == 1 )  THEN
     2629             DO  k = nzb+1, nzt
     2630                chem_species(ilsp)%tconc_m(k,j,i) = tend(k,j,i)
     2631             ENDDO
     2632          ELSEIF ( intermediate_timestep_count < &
     2633               intermediate_timestep_count_max )  THEN
     2634             DO  k = nzb+1, nzt
     2635                chem_species(ilsp)%tconc_m(k,j,i) = -9.5625_wp * tend(k,j,i) +                     &
     2636                     5.3125_wp * chem_species(ilsp)%tconc_m(k,j,i)
     2637             ENDDO
     2638          ENDIF
     2639       ENDIF
     2640
    26752641    ENDDO
    2676 !
    2677 !-- Calculate tendencies for the next Runge-Kutta step
    2678     IF ( timestep_scheme(1:5) == 'runge' )  THEN
    2679        IF ( intermediate_timestep_count == 1 )  THEN
    2680           DO  k = nzb+1, nzt
    2681              tcs_scalar_m(k,j,i) = tend(k,j,i)
    2682           ENDDO
    2683        ELSEIF ( intermediate_timestep_count < &
    2684             intermediate_timestep_count_max )  THEN
    2685           DO  k = nzb+1, nzt
    2686              tcs_scalar_m(k,j,i) = -9.5625_wp * tend(k,j,i) + &
    2687                   5.3125_wp * tcs_scalar_m(k,j,i)
    2688           ENDDO
    2689        ENDIF
    2690     ENDIF
    26912642
    26922643 END SUBROUTINE chem_prognostic_equations_ij
     
    27042655    USE control_parameters
    27052656
    2706     USE indices
    2707 
    2708     USE pegrid
    2709 
    2710     IMPLICIT NONE
    27112657
    27122658    CHARACTER (LEN=20) :: spc_name_av !<   
     
    27782724
    27792725    USE arrays_3d
    2780     USE indices
    2781     USE kinds
    2782     USE pegrid
     2726
    27832727    USE statistics
    27842728
    2785     IMPLICIT NONE
    27862729
    27872730    CHARACTER (LEN=*) ::  mode   !<
     
    28372780 SUBROUTINE chem_swap_timelevel( level )
    28382781
    2839     IMPLICIT NONE
    28402782
    28412783    INTEGER(iwp), INTENT(IN) ::  level
     
    28682810 SUBROUTINE chem_wrd_local
    28692811
    2870 
    2871     IMPLICIT NONE
    28722812
    28732813    INTEGER(iwp) ::  lsp  !< running index for chem spcs.
     
    29532893         ONLY:  cos_zenith
    29542894
    2955 
    2956     IMPLICIT NONE
    29572895
    29582896    INTEGER(iwp), INTENT(IN) ::  i
     
    44704408!--               calc_stom_o3flux, frac_sto_o3_lu, fac_surface_area_2_PLA)
    44714409
    4472     IMPLICIT NONE
    44734410
    44744411    CHARACTER(LEN=*), INTENT(IN) ::  compnam         !< component name
     
    46384575 SUBROUTINE rc_special( icmp, compnam, lu, t, nwet, rc_tot, ready, ccomp_tot )
    46394576
    4640     IMPLICIT NONE
    46414577   
    46424578    CHARACTER(LEN=*), INTENT(IN)  ::  compnam     !< component name
     
    47104646 SUBROUTINE rc_gw( compnam, iratns, t, rh, nwet, sai_present, sai, gw )
    47114647
    4712     IMPLICIT NONE
    47134648!
    47144649!-- Input/output variables:
     
    47634698 SUBROUTINE rw_so2( t, nwet, rh, iratns, sai_present, gw )
    47644699
    4765     IMPLICIT NONE
    47664700!
    47674701!-- Input/output variables:
     
    48354769 SUBROUTINE rw_nh3_sutton( tsurf, rh,sai_present, gw )
    48364770
    4837     IMPLICIT NONE
    48384771!
    48394772!-- Input/output variables:
     
    48834816 SUBROUTINE rw_constant( rw_val, sai_present, gw )
    48844817
    4885     IMPLICIT NONE
    48864818!
    48874819!-- Input/output variables:
     
    49094841 SUBROUTINE rc_gstom( icmp, compnam, lu, lai_present, lai, solar_rad, sinphi, t, rh, diffusivity, gstom, p )
    49104842
    4911     IMPLICIT NONE
    49124843!
    49134844!-- input/output variables:
     
    50064937!>     8 = other                 GR = grassland
    50074938!>     9 = desert                DE = desert
    5008 
    5009     IMPLICIT NONE
    50104939!
    50114940!-- Emberson specific declarations
     
    51445073 SUBROUTINE par_dir_diff( solar_rad, sinphi, pres, pres_0, par_dir, par_diff )
    51455074
    5146     IMPLICIT NONE
    51475075
    51485076    REAL(wp), INTENT(IN) ::  solar_rad       !< solar radiation, dirict+diffuse (W m-2)
     
    52115139 SUBROUTINE rc_get_vpd( temp, rh, vpd )
    52125140
    5213     IMPLICIT NONE
    52145141!
    52155142!-- Input/output variables:
     
    52425169 SUBROUTINE rc_gsoil_eff( icmp, lu, sai, ust, nwet, t, gsoil_eff )
    52435170
    5244     IMPLICIT NONE
    52455171!
    52465172!-- Input/output variables:
     
    53335259 !-------------------------------------------------------------------
    53345260 SUBROUTINE rc_rinc( lu, sai, ust, rinc )
    5335 
    5336     IMPLICIT NONE
    53375261
    53385262!
     
    53765300 !-------------------------------------------------------------------
    53775301 SUBROUTINE rc_rctot( gstom, gsoil_eff, gw, gc_tot, rc_tot )
    5378 
    5379     IMPLICIT NONE
    53805302
    53815303!
     
    54635385! SUBROUTINE rc_comp_point_rc_eff( ccomp_tot, conc_ijk_ugm3, ra, rb, rc_tot, rc_eff )
    54645386!
    5465 !    IMPLICIT NONE
    54665387!
    54675388!!-- Input/output variables:
     
    55225443 ELEMENTAL FUNCTION sedimentation_velocity( rhopart, partsize, slipcor, visc ) RESULT( vs )
    55235444
    5524     IMPLICIT NONE
    5525 
    55265445!
    55275446!-- in/out
     
    55485467 SUBROUTINE drydepo_aero_zhang_vd( vd, rs, vs1, partsize, slipcor, nwet, tsurf, dens1, viscos1, &
    55495468      luc, ftop_lu, ustar )
    5550 
    5551     IMPLICIT NONE 
    55525469
    55535470!
     
    56525569 !-------------------------------------------------------------------------------------
    56535570 SUBROUTINE get_rb_cell( is_water, z0h, ustar, diffusivity, rb )   
    5654 
    5655 
    5656     IMPLICIT NONE
    56575571
    56585572!
     
    57125626 ELEMENTAL FUNCTION watervaporpartialpressure( q, p ) RESULT( p_w )
    57135627
    5714     IMPLICIT NONE
    5715 
    57165628!
    57175629!-- in/out
     
    57535665 ELEMENTAL FUNCTION saturationvaporpressure( t ) RESULT( e_sat_w )
    57545666
    5755 
    5756     IMPLICIT NONE
    5757 
    57585667!
    57595668!-- in/out
     
    57825691 ELEMENTAL FUNCTION relativehumidity_from_specifichumidity( q, t, p ) RESULT( rh )
    57835692
    5784 
    5785     IMPLICIT NONE
    5786 
    57875693!
    57885694!-- in/out
  • palm/trunk/SOURCE/module_interface.f90

    r3878 r3880  
    168168              chem_actions,                                                    &
    169169              chem_non_transport_physics,                                      &
     170              chem_prognostic_equations,                                       &
    170171              chem_swap_timelevel,                                             &
    171172              chem_3d_data_averaging,                                          &
     
    970971
    971972    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations()
     973    IF ( air_chemistry       )  CALL chem_prognostic_equations()
    972974    IF ( gust_module_enabled )  CALL gust_prognostic_equations()
    973975    IF ( ocean_mode          )  CALL ocean_prognostic_equations()
     
    993995
    994996    IF ( bulk_cloud_model    )  CALL bcm_prognostic_equations( i, j, i_omp_start, tn )
     997    IF ( air_chemistry       )  CALL chem_prognostic_equations( i, j, i_omp_start, tn )
    995998    IF ( gust_module_enabled )  CALL gust_prognostic_equations( i, j, i_omp_start, tn )
    996999    IF ( ocean_mode          )  CALL ocean_prognostic_equations( i, j, i_omp_start, tn )
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3879 r3880  
    387387        ONLY:  buoyancy
    388388
    389     USE chem_modules,                                                          &
    390         ONLY:  chem_gasphase_on, deposition_dry, chem_species
    391 
    392     USE chem_gasphase_mod,                                                     &
    393         ONLY:  nspec, spc_names
    394 
    395389    USE chemistry_model_mod,                                                   &
    396         ONLY:  chem_boundary_conds_decycle, chem_prognostic_equations
     390        ONLY:  chem_boundary_conds_decycle
    397391
    398392    USE control_parameters,                                                    &
     
    518512
    519513    LOGICAL      ::  loop_start          !<
    520     INTEGER(iwp) ::  lsp
    521514
    522515
     
    11131106          CALL module_interface_prognostic_equations( i, j, i_omp_start, tn )
    11141107
    1115 !
    1116 !--       Calculate prognostic equation for chemical quantites
    1117           IF ( air_chemistry )  THEN
    1118              !> TODO: remove time measurement since it slows down performance because it will be called extremely often
    1119 !
    1120 !--          Loop over chemical species
    1121              DO  lsp = 1, nspec
    1122                 CALL chem_prognostic_equations( chem_species(lsp)%conc_p,      &
    1123                                      chem_species(lsp)%conc,                   &
    1124                                      chem_species(lsp)%tconc_m,                &
    1125                                      chem_species(lsp)%conc_pr_init,           &
    1126                                      i, j, i_omp_start, tn, lsp,               &
    1127                                      chem_species(lsp)%flux_s_cs,              &
    1128                                      chem_species(lsp)%diss_s_cs,              &
    1129                                      chem_species(lsp)%flux_l_cs,              &
    1130                                      chem_species(lsp)%diss_l_cs )       
    1131              ENDDO
    1132 
    1133           ENDIF   ! Chemical equations
    1134 
    11351108       ENDDO  ! loop over j
    11361109    ENDDO  ! loop over i
     
    11601133    INTEGER(iwp) ::  j     !<
    11611134    INTEGER(iwp) ::  k     !<
    1162     INTEGER(iwp) ::  lsp   !< running index for chemical species
    11631135
    11641136    REAL(wp)     ::  sbt  !<
     
    18951867    CALL module_interface_prognostic_equations()
    18961868
    1897 !
    1898 !-- Calculate prognostic equation for chemical quantites
    1899     IF ( air_chemistry )  THEN
    1900        CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'start' )
    1901 !
    1902 !--    Loop over chemical species
    1903        DO  lsp = 1, nspec
    1904           CALL chem_prognostic_equations( chem_species(lsp)%conc_p,            &
    1905                                           chem_species(lsp)%conc,              &
    1906                                           chem_species(lsp)%tconc_m,           &
    1907                                           chem_species(lsp)%conc_pr_init,      &
    1908                                           lsp )
    1909        ENDDO
    1910 
    1911        CALL cpu_log( log_point_s(25), 'chem.advec+diff+prog', 'stop' )             
    1912     ENDIF   ! Chemicals equations
    1913 
    19141869 END SUBROUTINE prognostic_equations_vector
    19151870
Note: See TracChangeset for help on using the changeset viewer.