Ignore:
Timestamp:
Dec 18, 2015 1:56:05 PM (8 years ago)
Author:
raasch
Message:

bugfixes for calculations in statistical regions which do not contain grid points in the lowest vertical levels, mean surface level height considered in the calculation of the characteristic vertical velocity

File:
1 edited

Legend:

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

    r1735 r1738  
    1919! Current revisions:
    2020! ------------------
    21 !
     21! calculate mean surface level height for each statistic region
    2222!
    2323! Former revisions:
     
    273273   
    274274    USE statistics,                                                            &
    275         ONLY:  hom, hom_sum, pr_palm, rmask, spectrum_x, spectrum_y,           &
    276                statistic_regions, sums, sums_divnew_l, sums_divold_l, sums_l, &
    277                sums_l_l, sums_up_fraction_l, sums_wsts_bc_l, ts_value,         &
    278                var_d, weight_pres, weight_substep
     275        ONLY:  hom, hom_sum, mean_surface_level_height, pr_palm, rmask,        &
     276               spectrum_x, spectrum_y, statistic_regions, sums, sums_divnew_l, &
     277               sums_divold_l, sums_l, sums_l_l, sums_up_fraction_l,            &
     278               sums_wsts_bc_l, ts_value, var_d, weight_pres, weight_substep
    279279 
    280280    USE surface_layer_fluxes_mod,                                              &
     
    299299    REAL(wp), DIMENSION(1:2) ::  volume_flow_initial_l  !<
    300300
     301    REAL(wp), DIMENSION(:), ALLOCATABLE ::  mean_surface_level_height_l    !<
    301302    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner_l    !<
    302303    REAL(wp), DIMENSION(:), ALLOCATABLE ::  ngp_3d_inner_tmp  !<
     
    306307!
    307308!-- Allocate arrays
    308     ALLOCATE( ngp_2dh(0:statistic_regions), ngp_2dh_l(0:statistic_regions), &
     309    ALLOCATE( mean_surface_level_height(0:statistic_regions),               &
     310              mean_surface_level_height_l(0:statistic_regions),             &
     311              ngp_2dh(0:statistic_regions), ngp_2dh_l(0:statistic_regions), &
    309312              ngp_3d(0:statistic_regions),                                  &
    310313              ngp_3d_inner(0:statistic_regions),                            &
     
    18201823!
    18211824!-- Compute total sum of active mask grid points
     1825!-- and the mean surface level height for each statistic region
    18221826!-- ngp_2dh: number of grid points of a horizontal cross section through the
    18231827!--          total domain
     
    18341838    ngp_sums          = ( nz + 2 ) * ( pr_palm + max_pr_user )
    18351839
     1840    mean_surface_level_height   = 0.0_wp
     1841    mean_surface_level_height_l = 0.0_wp
     1842
    18361843    DO  sr = 0, statistic_regions
    18371844       DO  i = nxl, nxr
     
    18411848!--             All xy-grid points
    18421849                ngp_2dh_l(sr) = ngp_2dh_l(sr) + 1
     1850                mean_surface_level_height_l(sr) = mean_surface_level_height_l(sr) + &
     1851                                                  zw(nzb_s_inner(j,i))
    18431852!
    18441853!--             xy-grid points above topography
     
    18731882                        MPI_SUM, comm2d, ierr )
    18741883    ngp_3d_inner = INT( ngp_3d_inner_tmp, KIND = SELECTED_INT_KIND( 18 ) )
     1884    IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
     1885    CALL MPI_ALLREDUCE( mean_surface_level_height_l(0),                       &
     1886                        mean_surface_level_height(0), sr, MPI_REAL,           &
     1887                        MPI_SUM, comm2d, ierr )
     1888    mean_surface_level_height = mean_surface_level_height / REAL( ngp_2dh )
    18751889#else
    18761890    ngp_2dh         = ngp_2dh_l
     
    18781892    ngp_2dh_s_inner = ngp_2dh_s_inner_l
    18791893    ngp_3d_inner    = INT( ngp_3d_inner_l, KIND = SELECTED_INT_KIND( 18 ) )
     1894    mean_surface_level_height = mean_surface_level_height_l / REAL( ngp_2dh_l )
    18801895#endif
    18811896
     
    18921907    ngp_2dh_s_inner = MAX( 1, ngp_2dh_s_inner(:,:) )
    18931908
    1894     DEALLOCATE( ngp_2dh_l, ngp_2dh_outer_l, ngp_3d_inner_l, ngp_3d_inner_tmp )
     1909    DEALLOCATE( mean_surface_level_height_l, ngp_2dh_l, ngp_2dh_outer_l,      &
     1910                ngp_3d_inner_l, ngp_3d_inner_tmp )
    18951911
    18961912    CALL location_message( 'leaving init_3d_model', .TRUE. )
Note: See TracChangeset for help on using the changeset viewer.