Ignore:
Timestamp:
Feb 18, 2009 5:50:38 PM (15 years ago)
Author:
letzel
Message:
  • External pressure gradient (check_parameters, init_3d_model, header, modules, parin, prognostic_equations)
  • New topography case 'single_street_canyon'
File:
1 edited

Legend:

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

    r198 r240  
    77! Actual revisions:
    88! -----------------
    9 !
     9! Set the starting level and the vertical smoothing factor used for
     10! the external pressure gradient
    1011!
    1112! Former revisions:
     
    9192    IMPLICIT NONE
    9293
    93     INTEGER ::  i, j, k, sr
     94    INTEGER ::  i, ind_array(1), j, k, sr
    9495
    9596    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_2dh_l, ngp_3d_inner_l
     
    111112              sums_divnew_l(0:statistic_regions),                           &
    112113              sums_divold_l(0:statistic_regions) )
    113     ALLOCATE( rdf(nzb+1:nzt) )
     114    ALLOCATE( dp_smooth_factor(nzb:nzt), rdf(nzb+1:nzt) )
    114115    ALLOCATE( ngp_2dh_outer(nzb:nzt+1,0:statistic_regions),                 &
    115116              ngp_2dh_outer_l(nzb:nzt+1,0:statistic_regions),               &
     
    12641265
    12651266!
     1267!-- Initialize the starting level and the vertical smoothing factor used for
     1268!-- the external pressure gradient
     1269    dp_smooth_factor = 1.0
     1270    IF ( dp_external )  THEN
     1271!
     1272!--    Set the starting level dp_level_ind_b only if it has not been set before
     1273!--    (e.g. in init_grid).
     1274       IF ( dp_level_ind_b == 0 )  THEN
     1275          ind_array = MINLOC( ABS( dp_level_b - zu ) )
     1276          dp_level_ind_b = ind_array(1) - 1 + nzb
     1277                                        ! MINLOC uses lower array bound 1
     1278       ENDIF
     1279       IF ( dp_smooth )  THEN
     1280          dp_smooth_factor(:dp_level_ind_b) = 0.0
     1281          DO  k = dp_level_ind_b+1, nzt
     1282             dp_smooth_factor(k) = 0.5 * ( 1.0 + SIN( pi * &
     1283                  ( REAL( k - dp_level_ind_b ) /  &
     1284                    REAL( nzt - dp_level_ind_b ) - 0.5 ) ) )
     1285          ENDDO
     1286       ENDIF
     1287    ENDIF
     1288
     1289!
    12661290!-- Initialize diffusivities used within the outflow damping layer in case of
    12671291!-- non-cyclic lateral boundaries. A linear increase is assumed over the first
Note: See TracChangeset for help on using the changeset viewer.