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_write_exchange_statistics.f90

    r1321 r1359  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! New particle structure integrated.
    2323!
    2424! Former revisions:
     
    4747!------------------------------------------------------------------------------!
    4848
    49     USE control_parameters,                                                     &
     49    USE control_parameters,                                                    &
    5050        ONLY:  current_timestep_number, dt_3d, simulated_time
    5151
    52     USE particle_attributes,                                                    &
    53         ONLY:  maximum_number_of_particles, number_of_particles, trlp_count_sum,&
    54                trlp_count_recv_sum, trnp_count_sum, trnp_count_recv_sum,        &
    55                trrp_count_sum, trrp_count_recv_sum, trsp_count_sum,             &
    56                trsp_count_recv_sum
     52    USE indices,                                                               &
     53        ONLY:  nxl, nxr, nys, nyn, nzb, nzt
     54
     55    USE particle_attributes,                                                   &
     56        ONLY:  grid_particles, maximum_number_of_particles,                    &
     57               number_of_particles, particles, prt_count,                      &
     58               trlp_count_sum, trlp_count_recv_sum, trnp_count_sum,            &
     59               trnp_count_recv_sum, trrp_count_sum, trrp_count_recv_sum,       &
     60               trsp_count_sum, trsp_count_recv_sum
    5761
    5862    USE pegrid
     
    6064    IMPLICIT NONE
    6165
     66    INTEGER(iwp) :: ip         !:
     67    INTEGER(iwp) :: jp         !:
     68    INTEGER(iwp) :: kp         !:
     69
     70!
     71!-- Determine maximum number of particles (i.e., all possible particles that
     72!-- have been allocated) and the current number of particles
     73    number_of_particles         = 0
     74    maximum_number_of_particles = 0
     75    DO  ip = nxl, nxr
     76       DO  jp = nys, nyn
     77          DO  kp = nzb+1, nzt
     78             number_of_particles = number_of_particles                         &
     79                                     + prt_count(kp,jp,ip)
     80             maximum_number_of_particles = maximum_number_of_particles         &
     81                                     + SIZE(grid_particles(kp,jp,ip)%particles)
     82          ENDDO
     83       ENDDO
     84    ENDDO
    6285
    6386    CALL check_open( 80 )
     
    77100!
    78101!-- Formats
    79 8000 FORMAT (I6,1X,F7.2,4X,I6,5X,4(I3,1X,I4,'/',I4,2X),6X,I6)
     1028000 FORMAT (I6,1X,F7.2,4X,I10,5X,4(I3,1X,I4,'/',I4,2X),6X,I10)
    80103
    81104
Note: See TracChangeset for help on using the changeset viewer.