Ignore:
Timestamp:
Nov 9, 2020 1:40:05 PM (3 years ago)
Author:
raasch
Message:

first preliminary version for output of particle data time series

File:
1 edited

Legend:

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

    r4677 r4778  
    2424! -----------------
    2525! $Id$
     26! variables for particle output renamed, id counter removed from particle type
     27!
     28! 4677 2020-09-14 07:55:28Z raasch
    2629! file re-formatted to follow the PALM coding standard
    2730!
     
    6063    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
    6164
    62     CHARACTER(LEN=varnamelength), DIMENSION(50) ::  part_output = ' '  !< namelist parameter
     65    CHARACTER(LEN=64)                           ::  pts_id_file = ''  !< namelist parameter
     66    CHARACTER(LEN=varnamelength), DIMENSION(50) ::  data_output_pts = ''    !< namelist parameter
    6367
    6468    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
     
    7175                                                                  !< prt_count)
    7276    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
    73     INTEGER(iwp) ::  part_inc = 1                                 !< increment of particles in output file
     77    INTEGER(iwp) ::  pts_increment = 1                            !< increment of particles in output file
    7478
    7579    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
     
    8488                                                          !< number)
    8589    REAL(wp) ::  particle_advection_start = 0.0_wp        !< namelist parameter (see documentation)
    86     REAL(wp) ::  part_percent = 100.0_wp                  !< percentage of particles in output file
     90    REAL(wp) ::  pts_percentage = 100.0_wp                !< percentage of particles in output file
    8791
    8892    TYPE, PUBLIC ::  particle_type
     
    115119    END TYPE particle_type
    116120
    117     TYPE(particle_type), DIMENSION(:), POINTER ::  particles       !< Particle array for this grid cell
    118     TYPE(particle_type)                        ::  zero_particle   !< zero particle to avoid weird thinge
     121    TYPE(particle_type), DIMENSION(:), POINTER ::  particles      !< Particle array for this grid cell
     122    TYPE(particle_type)                        ::  zero_particle  !< zero particle to avoid weird things
    119123
    120124    TYPE particle_groups_type
     
    129133
    130134    TYPE  grid_particle_def
    131         INTEGER(iwp), DIMENSION(0:7)               ::  start_index        !< start particle index for current block
    132         INTEGER(iwp), DIMENSION(0:7)               ::  end_index          !< end particle index for current block
    133         INTEGER(iwp)                               ::  id_counter         !< particle id counter
    134         LOGICAL                                    ::  time_loop_done     !< timestep loop for particle advection
    135         TYPE(particle_type), POINTER, DIMENSION(:) ::  particles          !< Particle array for this grid cell
     135        INTEGER(iwp), DIMENSION(0:7)               ::  start_index     !< start particle index for current block
     136        INTEGER(iwp), DIMENSION(0:7)               ::  end_index       !< end particle index for current block
     137        LOGICAL                                    ::  time_loop_done  !< timestep loop for particle advection
     138        TYPE(particle_type), POINTER, DIMENSION(:) ::  particles       !< Particle array for this grid cell
    136139    END TYPE grid_particle_def
    137140
Note: See TracChangeset for help on using the changeset viewer.