Ignore:
Timestamp:
Jul 29, 2020 7:23:03 AM (4 years ago)
Author:
raasch
Message:

extensions required for MPI-I/O of particle data to restart files

File:
1 edited

Legend:

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

    r4360 r4628  
    2020! Current revisions:
    2121! ------------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! extensions required for MPI-I/O of particle data to restart files
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    4750    USE, INTRINSIC ::  ISO_C_BINDING
    4851
     52    USE control_parameters,                                                                        &
     53        ONLY: varnamelength
     54
    4955    USE kinds
     56
     57    CHARACTER(LEN=varnamelength), DIMENSION(50) ::  part_output = ' '  !< namelist parameter
    5058
    5159    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
     
    5462    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
    5563    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
     64    INTEGER(iwp) ::  number_of_output_particles = 0               !< number of output particles
    5665    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
    5766    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
     67    INTEGER(iwp) ::  part_inc = 1                                 !< increment of particles in output file
    5868
    5969    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
     
    6272   
    6373    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
     74    LOGICAL ::  unlimited_dimension = .TRUE.              !< umlimited dimension for particle output
    6475    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)   
    6576    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
    6677
    67     REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
    68     REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
     78    REAL(wp) ::  alloc_factor = 20.0_wp                   !< namelist parameter (see documentation)
     79    REAL(wp) ::  oversize = 100.0_wp                      !< reserve spare particles in output file (in % relative to initial number)
     80    REAL(wp) ::  particle_advection_start = 0.0_wp        !< namelist parameter (see documentation)
     81    REAL(wp) ::  part_percent = 100.0_wp                  !< percentage of particles in output file
    6982
    70 !
    71 !-- WARNING: For compatibility of derived types, the BIND attribute is required, and interoperable C
    72 !-- datatypes must be used. These type are hard wired here! So changes in working precision (wp, iwp)
    73 !-- will not affect the particle_type!
    74 !-- The main reason for introducing the interoperable datatypes was to avoid compiler warnings of
    75 !-- the gfortran compiler.
    76 !-- The BIND attribite is required because of C_F_POINTER usage in the pmc particle interface.
    77     TYPE, BIND(C) ::  particle_type
    78         REAL(C_DOUBLE) ::  aux1          !< auxiliary multi-purpose feature
    79         REAL(C_DOUBLE) ::  aux2          !< auxiliary multi-purpose feature
    80         REAL(C_DOUBLE) ::  radius        !< radius of particle
    81         REAL(C_DOUBLE) ::  age           !< age of particle
    82         REAL(C_DOUBLE) ::  age_m         !<
    83         REAL(C_DOUBLE) ::  dt_sum        !<
    84         REAL(C_DOUBLE) ::  e_m           !< interpolated sgs tke
    85         REAL(C_DOUBLE) ::  origin_x      !< origin x-position of particle (changed cyclic bc)
    86         REAL(C_DOUBLE) ::  origin_y      !< origin y-position of particle (changed cyclic bc)
    87         REAL(C_DOUBLE) ::  origin_z      !< origin z-position of particle (changed cyclic bc)
    88         REAL(C_DOUBLE) ::  rvar1         !<
    89         REAL(C_DOUBLE) ::  rvar2         !<
    90         REAL(C_DOUBLE) ::  rvar3         !<
    91         REAL(C_DOUBLE) ::  speed_x       !< speed of particle in x
    92         REAL(C_DOUBLE) ::  speed_y       !< speed of particle in y
    93         REAL(C_DOUBLE) ::  speed_z       !< speed of particle in z
    94         REAL(C_DOUBLE) ::  weight_factor !< weighting factor
    95         REAL(C_DOUBLE) ::  x             !< x-position
    96         REAL(C_DOUBLE) ::  y             !< y-position
    97         REAL(C_DOUBLE) ::  z             !< z-position
    98         INTEGER(C_INT) ::  class         !< radius class needed for collision
    99         INTEGER(C_INT) ::  group         !< number of particle group
    100         INTEGER(C_LONG_LONG) ::  id            !< particle ID (64 bit integer)
    101         LOGICAL(C_BOOL) ::  particle_mask !< if this parameter is set to false the particle will be deleted
    102         INTEGER(C_INT) ::  block_nr      !< number for sorting (removable?)
     83    TYPE, PUBLIC ::  particle_type
     84        REAL(wp)     ::  aux1          !< auxiliary multi-purpose feature
     85        REAL(wp)     ::  aux2          !< auxiliary multi-purpose feature
     86        REAL(wp)     ::  radius        !< radius of particle
     87        REAL(wp)     ::  age           !< age of particle
     88        REAL(wp)     ::  age_m         !<
     89        REAL(wp)     ::  dt_sum        !<
     90        REAL(wp)     ::  e_m           !< interpolated sgs tke
     91        REAL(wp)     ::  origin_x      !< origin x-position of particle (changed cyclic bc)
     92        REAL(wp)     ::  origin_y      !< origin y-position of particle (changed cyclic bc)
     93        REAL(wp)     ::  origin_z      !< origin z-position of particle (changed cyclic bc)
     94        REAL(wp)     ::  rvar1         !<
     95        REAL(wp)     ::  rvar2         !<
     96        REAL(wp)     ::  rvar3         !<
     97        REAL(wp)     ::  speed_x       !< speed of particle in x
     98        REAL(wp)     ::  speed_y       !< speed of particle in y
     99        REAL(wp)     ::  speed_z       !< speed of particle in z
     100        REAL(wp)     ::  weight_factor !< weighting factor
     101        REAL(wp)     ::  x             !< x-position
     102        REAL(wp)     ::  y             !< y-position
     103        REAL(wp)     ::  z             !< z-position
     104        INTEGER(iwp) ::  class         !< radius class needed for collision
     105        INTEGER(iwp) ::  group         !< number of particle group
     106        INTEGER(idp) ::  id            !< particle ID (64 bit integer)
     107        LOGICAL      ::  particle_mask !< if this parameter is set to false the particle will be deleted
     108        INTEGER(iwp) ::  block_nr      !< number for sorting (removable?)
     109        INTEGER(iwp) ::  particle_nr=-1   !< particle number for particle IO (increment one
    103110    END TYPE particle_type
    104111
Note: See TracChangeset for help on using the changeset viewer.