Ignore:
Timestamp:
Oct 2, 2018 12:21:11 PM (6 years ago)
Author:
kanani
Message:

Merge chemistry branch at r3297 to trunk

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE

  • palm/trunk/SOURCE/flow_statistics.f90

    r3294 r3298  
    1919!
    2020! Current revisions:
    21 ! -----------------
     21! ------------------
    2222!
    2323!
     
    2525! -----------------
    2626! $Id$
     27! - Minor formatting (kanani)
     28! - Added  .AND. max_pr_cs > 0 before MPI_ALLREDUCE call (forkel)
     29! - Data arrays, sums, sums_l, hom, hom_sum updated for chem species (basit)
     30! - Directives of parallelism added for chemistry (basit)
     31! - Call for chem_statistics added (basit)
     32!
     33! 3294 2018-10-01 02:37:10Z raasch
    2734! ocean renamed ocean_mode
    2835!
     
    283290!------------------------------------------------------------------------------!
    284291 SUBROUTINE flow_statistics
    285  
     292
    286293
    287294    USE arrays_3d,                                                             &
     
    291298               sa, u, ug, v, vg, vpt, w, w_subs, waterflux_output_conversion,  &
    292299               zw, d_exner
    293        
     300
    294301    USE basic_constants_and_equations_mod,                                     &
    295         ONLY:   g, lv_d_cp
    296        
     302        ONLY:  g, lv_d_cp
     303
     304
     305    USE chem_modules,                                                          &
     306        ONLY:  max_pr_cs
     307
     308    USE chemistry_model_mod,                                                   &
     309        ONLY:  chem_species, chem_statistics
     310
    297311    USE control_parameters,                                                    &
    298         ONLY:   average_count_pr, cloud_droplets, do_sum,                      &
     312        ONLY:   air_chemistry, average_count_pr, cloud_droplets, do_sum,       &
    299313                dt_3d, humidity, initializing_actions, land_surface,           &
    300314                large_scale_forcing, large_scale_subsidence, max_pr_user,      &
     
    303317                use_subsidence_tendencies, use_surface_fluxes, use_top_fluxes, &
    304318                ws_scheme_mom, ws_scheme_sca
    305        
     319
    306320    USE cpulog,                                                                &
    307321        ONLY:   cpu_log, log_point
    308        
     322
    309323    USE grid_variables,                                                        &
    310324        ONLY:   ddx, ddy
     
    17801794       ENDIF
    17811795!
     1796!--    Calculate the chemistry module profiles
     1797       IF ( air_chemistry ) THEN
     1798          CALL chem_statistics( 'profiles', sr, tn )
     1799       ENDIF
     1800!
    17821801!--    Calculate the user-defined profiles
    17831802       CALL user_statistics( 'profiles', sr, tn )
     
    17971816                                   sums_l(:,pr_palm+1:pr_palm+max_pr_user,i)
    17981817             ENDIF
     1818
     1819             IF ( air_chemistry )  THEN
     1820                IF ( max_pr_cs > 0 )  THEN                                 
     1821                     sums_l(:,pr_palm+max_pr_user+1:pr_palm + max_pr_user+ max_pr_cs,0) =          &
     1822                               sums_l(:,pr_palm+max_pr_user+1:pr_palm + max_pr_user+max_pr_cs,0) + &
     1823                               sums_l(:,pr_palm+max_pr_user+1:pr_palm + max_pr_user+max_pr_cs,i)
     1824
     1825                ENDIF
     1826             ENDIF
    17991827          ENDDO
    18001828       ENDIF
     
    18111839                              MPI_REAL, MPI_SUM, comm2d, ierr )
    18121840       ENDIF
     1841
     1842       IF ( air_chemistry .AND. max_pr_cs > 0 )  THEN
     1843          IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     1844             CALL MPI_ALLREDUCE( sums_l(nzb,pr_palm+1,0), sums(nzb,pr_palm+1), &
     1845                                 nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d, ierr )
     1846       ENDIF
     1847
    18131848#else
    18141849       sums = sums_l(:,:,0)
     
    18751910                                    ngp_2dh_s_inner(k,sr)
    18761911          ENDDO
     1912       ENDIF
     1913
     1914       IF ( air_chemistry ) THEN
     1915          IF ( max_pr_cs > 0 )  THEN                 
     1916             DO k = nzb, nzt+1
     1917                sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) = &
     1918                                 sums(k, pr_palm+1:pr_palm+max_pr_user+max_pr_cs) / &
     1919                                 ngp_2dh_s_inner(k,sr)
     1920             ENDDO
     1921          ENDIF 
    18771922       ENDIF
    18781923
     
    20182063       ENDIF
    20192064
     2065       IF ( air_chemistry )  THEN
     2066          IF ( max_pr_cs > 0 )  THEN    ! chem_spcs profiles     
     2067             hom(:, 1, pr_palm+max_pr_user+1:pr_palm + max_pr_user+max_pr_cs, sr) = &
     2068                               sums(:, pr_palm+max_pr_user+1:pr_palm+max_pr_user+max_pr_cs)
     2069          ENDIF
     2070       ENDIF
    20202071!
    20212072!--    Determine the boundary layer height using two different schemes.
Note: See TracChangeset for help on using the changeset viewer.