Ignore:
Timestamp:
May 30, 2017 5:47:52 PM (7 years ago)
Author:
suehring
Message:

Adjustments according new topography and surface-modelling concept implemented

File:
1 edited

Legend:

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

    r2224 r2232  
    2020! Current revisions:
    2121! -----------------
     22! Adjustments according to new topography realization
    2223!
    2324!
     
    146147
    147148    USE arrays_3d,                                                             &
    148         ONLY:  de_dx, de_dy, de_dz, zu, zw, z0
     149        ONLY:  de_dx, de_dy, de_dz, zu, zw
    149150
    150151    USE control_parameters,                                                    &
     
    157158    USE indices,                                                               &
    158159        ONLY:  nx, nxl, nxlg, nxrg, nxr, ny, nyn, nys, nyng, nysg, nz, nzb,    &
    159                nzb_w_inner, nzt
     160               nzb_max, nzt, wall_flags_0
    160161
    161162    USE kinds
     
    196197        ONLY:  random_function
    197198
     199    USE surface_mod,                                                           &
     200        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     201
    198202    IMPLICIT NONE
    199203
     
    287291       number_of_particle_groups = max_number_of_particle_groups
    288292    ENDIF
     293!
     294!-- Check if downward-facing walls exist. This case, reflection boundary
     295!-- conditions (as well as subgrid-scale velocities) may do not work
     296!-- propably (not realized so far).
     297    IF ( surf_def_h(1)%ns >= 1 )  THEN
     298       WRITE( message_string, * ) 'Overhanging topograpyh do not work '// &   
     299                                  'with particles'
     300       CALL message( 'lpm_init', 'PA0212', 0, 1, 0, 6, 0 )
     301
     302    ENDIF
    289303
    290304!
     
    355369       
    356370       ALLOCATE ( log_z_z0(0:number_of_sublayers) )
    357        z_p         = zu(nzb+1) - zw(nzb)
     371       z_p = zu(nzb+1) - zw(nzb)
    358372
    359373!
     
    362376!--    However, sensitivity studies showed that the effect is
    363377!--    negligible.
    364        z0_av_local  = SUM( z0(nys:nyn,nxl:nxr) )
     378       z0_av_local  = SUM( surf_def_h(0)%z0 ) + SUM( surf_lsm_h%z0 ) +         &
     379                      SUM( surf_usm_h%z0 )
    365380       z0_av_global = 0.0_wp
    366381
     
    577592    INTEGER(iwp)               ::  j           !< loop variable ( particles per point )
    578593    INTEGER(iwp)               ::  jp          !< index variable along y
     594    INTEGER(iwp)               ::  k           !< index variable along z
     595    INTEGER(iwp)               ::  k_surf      !< index of surface grid point
    579596    INTEGER(iwp)               ::  kp          !< index variable along z
    580597    INTEGER(iwp)               ::  loop_stride !< loop variable for initialization
     
    679696!
    680697!--                            Determine the grid indices of the particle position
    681                               ip = ( tmp_particle%x + 0.5_wp * dx ) * ddx
     698                               ip = ( tmp_particle%x + 0.5_wp * dx ) * ddx
    682699                               jp = ( tmp_particle%y + 0.5_wp * dy ) * ddy
    683700                               kp = tmp_particle%z / dz + 1 + offset_ocean_nzt
     701!
     702!--                            Determine surface level. Therefore, check for
     703!--                            upward-facing wall on w-grid. MAXLOC will return
     704!--                            the index of the lowest upward-facing wall.
     705                               k_surf = MAXLOC(                                &
     706                                             MERGE( 1, 0,                      &
     707                                   BTEST( wall_flags_0(nzb:nzb_max,jp,ip), 18 )&
     708                                                  ), DIM = 1                   &
     709                                              ) - 1
    684710
    685711                               IF ( seed_follows_topography )  THEN
    686712!
    687713!--                               Particle height is given relative to topography
    688                                   kp = kp + nzb_w_inner(jp,ip)
    689                                   tmp_particle%z = tmp_particle%z +            &
    690                                                          zw(nzb_w_inner(jp,ip))
    691                                   IF ( kp > nzt )  THEN
     714                                  kp = kp + k_surf
     715                                  tmp_particle%z = tmp_particle%z + zw(k_surf)
     716!--                               Skip particle release if particle position is
     717!--                               above model top, or within topography in case
     718!--                               of overhanging structures.
     719                                  IF ( kp > nzt  .OR.                          &
     720                                 .NOT. BTEST( wall_flags_0(kp,jp,ip), 0 ) )  THEN
    692721                                     pos_x = pos_x + pdx(i)
    693722                                     CYCLE xloop
    694723                                  ENDIF
     724!
     725!--                            Skip particle release if particle position is
     726!--                            below surface, or within topography in case
     727!--                            of overhanging structures.
    695728                               ELSEIF ( .NOT. seed_follows_topography .AND.    &
    696                                         tmp_particle%z <= zw(nzb_w_inner(jp,ip)) )  THEN
     729                                         tmp_particle%z <= zw(k_surf)  .OR.    &
     730                                        .NOT. BTEST( wall_flags_0(kp,jp,ip), 0 ) )&
     731                               THEN
    697732                                  pos_x = pos_x + pdx(i)
    698733                                  CYCLE xloop                               
     
    820855                                     pdx(particles(n)%group)
    821856                      particles(n)%x = particles(n)%x +                        &
    822                               MERGE( rand_contr, SIGN( dx, rand_contr ), &
     857                              MERGE( rand_contr, SIGN( dx, rand_contr ),       &
    823858                                     ABS( rand_contr ) < dx                    &
    824859                                   )
     
    828863                                     pdy(particles(n)%group)
    829864                      particles(n)%y = particles(n)%y +                        &
    830                               MERGE( rand_contr, SIGN( dy, rand_contr ), &
     865                              MERGE( rand_contr, SIGN( dy, rand_contr ),       &
    831866                                     ABS( rand_contr ) < dy                    &
    832867                                   )
     
    836871                                     pdz(particles(n)%group)
    837872                      particles(n)%z = particles(n)%z +                        &
    838                               MERGE( rand_contr, SIGN( dz, rand_contr ), &
     873                              MERGE( rand_contr, SIGN( dz, rand_contr ),       &
    839874                                     ABS( rand_contr ) < dz                    &
    840875                                   )
     
    854889                   i = ( particles(n)%x + 0.5_wp * dx ) * ddx
    855890                   j = ( particles(n)%y + 0.5_wp * dy ) * ddy
    856                    IF ( particles(n)%z <= zw(nzb_w_inner(j,i)) )  THEN
     891                   k =   particles(n)%z / dz + 1 + offset_ocean_nzt
     892!
     893!--                Check if particle is within topography
     894                   IF ( .NOT. BTEST( wall_flags_0(k,j,i), 0 ) )  THEN
    857895                      particles(n)%particle_mask = .FALSE.
    858896                      deleted_particles = deleted_particles + 1
    859897                   ENDIF
     898
    860899                ENDDO
    861900             ENDDO
Note: See TracChangeset for help on using the changeset viewer.