Ignore:
Timestamp:
Mar 6, 2019 4:58:03 PM (5 years ago)
Author:
raasch
Message:

unused variables removed, interoperable C datatypes introduced in particle type to avoid compiler warnings

File:
1 edited

Legend:

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

    r3720 r3786  
    2525! -----------------
    2626! $Id$
     27! interoperable C datatypes introduced in particle type to avoid compiler warnings
     28!
     29! 3720 2019-02-06 13:19:55Z knoop
    2730! time_prel replaced by last_particle_release_time
    2831!
     
    217220    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0)
    218221
    219 
     222!
     223!-- WARNING: For compatibility of derived types, the BIND attribute is required, and interoperable C
     224!-- datatypes must be used. These type are hard wired here! So changes in working precision (wp, iwp)
     225!-- will not affect the particle_type!
     226!-- The main reason for introducing the interoperable datatypes was to avoid compiler warnings of
     227!-- the gfortran compiler.
     228!-- The BIND attribite is required because of C_F_POINTER usage in the pmc particle interface.
    220229    TYPE, BIND(C) ::  particle_type
    221         REAL(wp)    ::  aux1          !< auxiliary multi-purpose feature
    222         REAL(wp)    ::  aux2          !< auxiliary multi-purpose feature
    223         REAL(wp)    ::  radius        !< radius of particle
    224         REAL(wp)    ::  age           !< age of particle
    225         REAL(wp)    ::  age_m         !<
    226         REAL(wp)    ::  dt_sum        !<
    227         REAL(wp)    ::  e_m           !< interpolated sgs tke
    228         REAL(wp)    ::  origin_x      !< origin x-position of particle (changed cyclic bc)
    229         REAL(wp)    ::  origin_y      !< origin y-position of particle (changed cyclic bc)
    230         REAL(wp)    ::  origin_z      !< origin z-position of particle (changed cyclic bc)
    231         REAL(wp)    ::  rvar1         !<
    232         REAL(wp)    ::  rvar2         !<
    233         REAL(wp)    ::  rvar3         !<
    234         REAL(wp)    ::  speed_x       !< speed of particle in x
    235         REAL(wp)    ::  speed_y       !< speed of particle in y
    236         REAL(wp)    ::  speed_z       !< speed of particle in z
    237         REAL(wp)    ::  weight_factor !< weighting factor
    238         REAL(wp)    ::  x             !< x-position
    239         REAL(wp)    ::  y             !< y-position
    240         REAL(wp)    ::  z             !< z-position
    241         INTEGER(iwp) ::  class         !< radius class needed for collision
    242         INTEGER(iwp) ::  group         !< number of particle group
    243         INTEGER(idp) ::  id            !< particle ID (64 bit integer)
     230        REAL(C_DOUBLE) ::  aux1          !< auxiliary multi-purpose feature
     231        REAL(C_DOUBLE) ::  aux2          !< auxiliary multi-purpose feature
     232        REAL(C_DOUBLE) ::  radius        !< radius of particle
     233        REAL(C_DOUBLE) ::  age           !< age of particle
     234        REAL(C_DOUBLE) ::  age_m         !<
     235        REAL(C_DOUBLE) ::  dt_sum        !<
     236        REAL(C_DOUBLE) ::  e_m           !< interpolated sgs tke
     237        REAL(C_DOUBLE) ::  origin_x      !< origin x-position of particle (changed cyclic bc)
     238        REAL(C_DOUBLE) ::  origin_y      !< origin y-position of particle (changed cyclic bc)
     239        REAL(C_DOUBLE) ::  origin_z      !< origin z-position of particle (changed cyclic bc)
     240        REAL(C_DOUBLE) ::  rvar1         !<
     241        REAL(C_DOUBLE) ::  rvar2         !<
     242        REAL(C_DOUBLE) ::  rvar3         !<
     243        REAL(C_DOUBLE) ::  speed_x       !< speed of particle in x
     244        REAL(C_DOUBLE) ::  speed_y       !< speed of particle in y
     245        REAL(C_DOUBLE) ::  speed_z       !< speed of particle in z
     246        REAL(C_DOUBLE) ::  weight_factor !< weighting factor
     247        REAL(C_DOUBLE) ::  x             !< x-position
     248        REAL(C_DOUBLE) ::  y             !< y-position
     249        REAL(C_DOUBLE) ::  z             !< z-position
     250        INTEGER(C_INT) ::  class         !< radius class needed for collision
     251        INTEGER(C_INT) ::  group         !< number of particle group
     252        INTEGER(C_LONG_LONG) ::  id            !< particle ID (64 bit integer)
    244253        LOGICAL(C_BOOL) ::  particle_mask !< if this parameter is set to false the particle will be deleted
    245         INTEGER(iwp) ::  block_nr      !< number for sorting (removable?)
     254        INTEGER(C_INT) ::  block_nr      !< number for sorting (removable?)
    246255    END TYPE particle_type
    247256
Note: See TracChangeset for help on using the changeset viewer.