Ignore:
Timestamp:
Apr 11, 2014 5:15:14 PM (10 years ago)
Author:
hoffmann
Message:

new Lagrangian particle structure integrated

File:
1 edited

Legend:

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

    r1321 r1359  
    2020! Current revisions:
    2121! ------------------
     22! New particle structure integrated.
     23! Kind definition added to all floating point numbers.
    2224!
    2325! Former revisions:
     
    6870
    6971    USE particle_attributes,                                                   &
    70         ONLY:  particles, prt_count, prt_start_index
     72        ONLY:  grid_particles, number_of_particles, particles, prt_count
    7173
    7274    IMPLICIT NONE
     
    7880    INTEGER(iwp) ::  psi !:
    7981
    80 
    8182    CALL cpu_log( log_point_s(45), 'lpm_calc_ql', 'start' )
    8283
    8384!
    8485!-- Set water content initially to zero
    85     ql = 0.0;  ql_v = 0.0;  ql_vp = 0.0
     86    ql = 0.0_wp;  ql_v = 0.0_wp;  ql_vp = 0.0_wp
    8687
    8788!
     
    8990    DO  i = nxl, nxr
    9091       DO  j = nys, nyn
    91           DO  k = nzb, nzt+1
     92          DO  k = nzb+1, nzt
     93
     94             number_of_particles = prt_count(k,j,i)
     95             IF ( number_of_particles <= 0 )  CYCLE
     96             particles => grid_particles(k,j,i)%particles(1:number_of_particles)
    9297
    9398!
    9499!--          Calculate the total volume in the boxes (ql_v, weighting factor
    95100!--          has to beincluded)
    96              psi = prt_start_index(k,j,i)
    97              DO  n = psi, psi+prt_count(k,j,i)-1
     101             DO  n = 1, prt_count(k,j,i)
    98102                ql_v(k,j,i)  = ql_v(k,j,i)  + particles(n)%weight_factor *  &
    99103                                              particles(n)%radius**3
     
    102106!
    103107!--          Calculate the liquid water content
    104              IF ( ql_v(k,j,i) /= 0.0 )  THEN
    105                 ql(k,j,i) = ql(k,j,i) + rho_l * 1.33333333 * pi *           &
     108             IF ( ql_v(k,j,i) /= 0.0_wp )  THEN
     109                ql(k,j,i) = ql(k,j,i) + rho_l * 1.33333333_wp * pi *           &
    106110                                        ql_v(k,j,i) /                       &
    107111                                        ( rho_surface * dx * dy * dz )
    108112
    109                 IF ( ql(k,j,i) < 0.0 ) THEN
     113                IF ( ql(k,j,i) < 0.0_wp ) THEN
    110114                   WRITE( message_string, * )  'LWC out of range: ' , &
    111                                                ql(k,j,i)
     115                                               ql(k,j,i),i,j,k
    112116                   CALL message( 'lpm_calc_liquid_water_content', '', 2, 2, &
    113117                                 -1, 6, 1 )
     
    116120             ELSE
    117121
    118                 ql(k,j,i) = 0.0
     122                ql(k,j,i) = 0.0_wp
    119123
    120124             ENDIF
Note: See TracChangeset for help on using the changeset viewer.