Ignore:
Timestamp:
Mar 27, 2015 9:56:27 AM (9 years ago)
Author:
raasch
Message:

optimized multigrid method installed, new parameter seed_follows_topography for particle release, small adjustment in subjob for HLRN

File:
1 edited

Legend:

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

    r1360 r1575  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! initial vertical particle position is allowed to follow the topography
    2323!
    2424! Former revisions:
     
    101101
    102102    USE indices,                                                               &
    103         ONLY:  nx, nxl, nxlg, nxrg, nxr, ny, nyn, nys, nyng, nysg, nz, nzb, nzt
     103        ONLY:  nx, nxl, nxlg, nxrg, nxr, ny, nyn, nys, nyng, nysg, nz, nzb,    &
     104               nzb_w_inner, nzt
    104105
    105106    USE kinds
     
    126127                prt_count, psb, psl, psn, psr, pss, pst,                       &
    127128                radius, random_start_position, read_particles_from_restartfile,&
    128                 skip_particles_for_tail, sort_count,                           &
     129                seed_follows_topography, skip_particles_for_tail, sort_count,  &
    129130                tail_mask, total_number_of_particles, total_number_of_tails,   &
    130131                use_particle_tails, use_sgs_for_particles,                     &
     
    649650                   pos_x = psl(i)
    650651
    651                   DO WHILE ( pos_x <= psr(i) )
     652            xloop: DO WHILE ( pos_x <= psr(i) )
    652653
    653654                      IF ( pos_x >= ( nxl - 0.5_wp ) * dx  .AND.  &
     
    738739                               tmp_particle%tail_id    = 0
    739740                            ENDIF
     741!
     742!--                         Determine the grid indices of the particle position
    740743                            ip = ( tmp_particle%x + 0.5_wp * dx ) * ddx
    741744                            jp = ( tmp_particle%y + 0.5_wp * dy ) * ddy
    742745                            kp = tmp_particle%z / dz + 1 + offset_ocean_nzt_m1
     746
     747                            IF ( seed_follows_topography )  THEN
     748!
     749!--                            Particle height is given relative to topography
     750                               kp = kp + nzb_w_inner(jp,ip)
     751                               tmp_particle%z = tmp_particle%z + zw(kp)
     752                               IF ( kp > nzt )  THEN
     753                                  pos_x = pos_x + pdx(i)
     754                                  CYCLE xloop
     755                               ENDIF
     756                            ENDIF
    743757
    744758                            local_count(kp,jp,ip) = local_count(kp,jp,ip) + 1
     
    758772                      pos_x = pos_x + pdx(i)
    759773
    760                    ENDDO
     774                   ENDDO xloop
    761775
    762776                ENDIF
Note: See TracChangeset for help on using the changeset viewer.