Ignore:
Timestamp:
Mar 14, 2014 6:25:17 PM (10 years ago)
Author:
suehring
Message:

Vertical logarithmic interpolation of horizontal particle speed for particles
between roughness height and first vertical grid level.

File:
1 edited

Legend:

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

    r1310 r1314  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Vertical logarithmic interpolation of horizontal particle speed for particles
     23! between roughness height and first vertical grid level.
    2324!
    2425! Former revisions:
     
    110111    IMPLICIT NONE
    111112
    112     INTEGER ::  i, j, n, nn
     113    INTEGER ::  i, j, k, n, nn
    113114#if defined( __parallel )
    114115    INTEGER, DIMENSION(3) ::  blocklengths, displacements, types
    115116#endif
    116117    LOGICAL ::  uniform_particles_l
    117     REAL    ::  pos_x, pos_y, pos_z
     118    REAL    ::  height_int, height_p, pos_x, pos_y, pos_z, z_p,            &
     119                z0_av_local = 0.0
    118120
    119121
     
    184186                 de_dy(nzb:nzt+1,nysg:nyng,nxlg:nxrg), &
    185187                 de_dz(nzb:nzt+1,nysg:nyng,nxlg:nxrg) )
     188    ENDIF
     189
     190!
     191!-- Allocate array required for logarithmic vertical interpolation of
     192!-- horizontal particle velocities between the surface and the first vertical
     193!-- grid level. In order to avoid repeated CPU cost-intensive CALLS of
     194!-- intrinsic FORTRAN procedure LOG(z/z0), LOG(z/z0) is precalculated for
     195!-- several heights. Splitting into 20 sublayers turned out to be sufficient.
     196!-- To obtain exact height levels of particles, linear interpolation is applied
     197!-- (see lpm_advec.f90).
     198    IF ( prandtl_layer )  THEN
     199       
     200       ALLOCATE ( log_z_z0(0:number_of_sublayers) )
     201       z_p         = zu(nzb+1) - zw(nzb)
     202
     203!
     204!--    Calculate horizontal mean value of z0 used for logartihmic
     205!--    interpolation. Note: this is not exact for heterogeneous z0.
     206!--    However, sensitivity studies showed that the effect is
     207!--    negligible.
     208       z0_av_local  = SUM( z0(nys:nyn,nxl:nxr) )
     209       z0_av_global = 0.0
     210
     211       CALL MPI_ALLREDUCE(z0_av_local, z0_av_global, 1, MPI_REAL, MPI_SUM, &
     212                          comm2d, ierr )
     213
     214       z0_av_global = z0_av_global  / ( ( ny + 1 ) * ( nx + 1 ) )
     215!
     216!--    Horizontal wind speed is zero below and at z0
     217       log_z_z0(0) = 0.0   
     218!
     219!--    Calculate vertical depth of the sublayers
     220       height_int  = ( z_p - z0_av_global ) / REAL( number_of_sublayers )
     221!
     222!--    Precalculate LOG(z/z0)
     223       height_p    = 0.0
     224       DO  k = 1, number_of_sublayers
     225
     226          height_p    = height_p + height_int
     227          log_z_z0(k) = LOG( height_p / z0_av_global )
     228
     229       ENDDO
     230
     231
    186232    ENDIF
    187233
Note: See TracChangeset for help on using the changeset viewer.