Ignore:
Timestamp:
Dec 6, 2017 4:03:27 PM (6 years ago)
Author:
raasch
Message:

file attributes and activation strings in .palm.iofiles revised, file extensions for nesting, masked output, wind turbine data, etc. changed

File:
1 edited

Legend:

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

    r2575 r2669  
    2525! -----------------
    2626! $Id$
     27! CONTIGUOUS-attribut added to 3d pointer arrays,
     28! coupling_char extended to LEN=8
     29!
     30! 2575 2017-10-24 09:57:58Z maronga
    2731! Renamed phi -> latitude, moved longitude from radiation model to modules
    2832!
     
    776780    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, TARGET ::  w_3     !< pointer for swapping of timelevels for respective quantity
    777781
    778     REAL(wp), DIMENSION(:,:,:), POINTER ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
    779     REAL(wp), DIMENSION(:,:,:), POINTER ::  e_p        !< pointer: prognostic value of sgs tke
    780     REAL(wp), DIMENSION(:,:,:), POINTER ::  nc         !< pointer: cloud drop number density
    781     REAL(wp), DIMENSION(:,:,:), POINTER ::  nc_p       !< pointer: prognostic value of cloud drop number density
    782     REAL(wp), DIMENSION(:,:,:), POINTER ::  nr         !< pointer: rain drop number density
    783     REAL(wp), DIMENSION(:,:,:), POINTER ::  nr_p       !< pointer: prognostic value of rain drop number density
    784     REAL(wp), DIMENSION(:,:,:), POINTER ::  prho       !< pointer: potential density
    785     REAL(wp), DIMENSION(:,:,:), POINTER ::  pt         !< pointer: potential temperature
    786     REAL(wp), DIMENSION(:,:,:), POINTER ::  pt_p       !< pointer: prognostic value of potential temperature
    787     REAL(wp), DIMENSION(:,:,:), POINTER ::  q          !< pointer: specific humidity
    788     REAL(wp), DIMENSION(:,:,:), POINTER ::  q_p        !< pointer: prognostic value of specific humidity
    789     REAL(wp), DIMENSION(:,:,:), POINTER ::  qc         !< pointer: cloud water content
    790     REAL(wp), DIMENSION(:,:,:), POINTER ::  qc_p       !< pointer: cloud water content
    791     REAL(wp), DIMENSION(:,:,:), POINTER ::  ql         !< pointer: liquid water content
    792     REAL(wp), DIMENSION(:,:,:), POINTER ::  ql_c       !< pointer: change in liquid water content due to
    793                                                        !< condensation/evaporation during last time step
    794     REAL(wp), DIMENSION(:,:,:), POINTER ::  qr         !< pointer: rain water content
    795     REAL(wp), DIMENSION(:,:,:), POINTER ::  qr_p       !< pointer: prognostic value of rain water content
    796     REAL(wp), DIMENSION(:,:,:), POINTER ::  rho_ocean  !< pointer: density of ocean
    797     REAL(wp), DIMENSION(:,:,:), POINTER ::  s          !< pointer: passive scalar
    798     REAL(wp), DIMENSION(:,:,:), POINTER ::  s_p        !< pointer: prognostic value of passive scalar
    799     REAL(wp), DIMENSION(:,:,:), POINTER ::  sa         !< pointer: ocean salinity
    800     REAL(wp), DIMENSION(:,:,:), POINTER ::  sa_p       !< pointer: prognostic value of ocean salinity
    801     REAL(wp), DIMENSION(:,:,:), POINTER ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
    802     REAL(wp), DIMENSION(:,:,:), POINTER ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
    803     REAL(wp), DIMENSION(:,:,:), POINTER ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
    804     REAL(wp), DIMENSION(:,:,:), POINTER ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
    805     REAL(wp), DIMENSION(:,:,:), POINTER ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
    806     REAL(wp), DIMENSION(:,:,:), POINTER ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
    807     REAL(wp), DIMENSION(:,:,:), POINTER ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
    808     REAL(wp), DIMENSION(:,:,:), POINTER ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
    809     REAL(wp), DIMENSION(:,:,:), POINTER ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
    810     REAL(wp), DIMENSION(:,:,:), POINTER ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
    811     REAL(wp), DIMENSION(:,:,:), POINTER ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
    812     REAL(wp), DIMENSION(:,:,:), POINTER ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
    813     REAL(wp), DIMENSION(:,:,:), POINTER ::  u          !< pointer: horizontal velocity component u (x-direction)
    814     REAL(wp), DIMENSION(:,:,:), POINTER ::  u_p        !< pointer: prognostic value of u
    815     REAL(wp), DIMENSION(:,:,:), POINTER ::  v          !< pointer: horizontal velocity component v (y-direction)
    816     REAL(wp), DIMENSION(:,:,:), POINTER ::  v_p        !< pointer: prognostic value of v
    817     REAL(wp), DIMENSION(:,:,:), POINTER ::  vpt        !< pointer: virtual potential temperature
    818     REAL(wp), DIMENSION(:,:,:), POINTER ::  w          !< pointer: vertical velocity component w (z-direction)
    819     REAL(wp), DIMENSION(:,:,:), POINTER ::  w_p        !< pointer: prognostic value of w
     782    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e          !< pointer: subgrid-scale turbulence kinetic energy (sgs tke)
     783    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  e_p        !< pointer: prognostic value of sgs tke
     784    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc         !< pointer: cloud drop number density
     785    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nc_p       !< pointer: prognostic value of cloud drop number density
     786    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr         !< pointer: rain drop number density
     787    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  nr_p       !< pointer: prognostic value of rain drop number density
     788    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  prho       !< pointer: potential density
     789    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt         !< pointer: potential temperature
     790    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  pt_p       !< pointer: prognostic value of potential temperature
     791    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q          !< pointer: specific humidity
     792    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  q_p        !< pointer: prognostic value of specific humidity
     793    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc         !< pointer: cloud water content
     794    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qc_p       !< pointer: cloud water content
     795    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql         !< pointer: liquid water content
     796    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ql_c       !< pointer: change in liquid water content due to
     797                                                                   !< condensation/evaporation during last time step
     798    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr         !< pointer: rain water content
     799    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  qr_p       !< pointer: prognostic value of rain water content
     800    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  rho_ocean  !< pointer: density of ocean
     801    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s          !< pointer: passive scalar
     802    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  s_p        !< pointer: prognostic value of passive scalar
     803    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa         !< pointer: ocean salinity
     804    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  sa_p       !< pointer: prognostic value of ocean salinity
     805    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  te_m       !< pointer: weighted tendency of e for previous sub-timestep (Runge-Kutta)
     806    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnc_m      !< pointer: weighted tendency of nc for previous sub-timestep (Runge-Kutta)
     807    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tnr_m      !< pointer: weighted tendency of nr for previous sub-timestep (Runge-Kutta)
     808    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tpt_m      !< pointer: weighted tendency of pt for previous sub-timestep (Runge-Kutta)
     809    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tq_m       !< pointer: weighted tendency of q for previous sub-timestep (Runge-Kutta)
     810    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqc_m      !< pointer: weighted tendency of qc for previous sub-timestep (Runge-Kutta)
     811    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tqr_m      !< pointer: weighted tendency of qr for previous sub-timestep (Runge-Kutta)
     812    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  ts_m       !< pointer: weighted tendency of s for previous sub-timestep (Runge-Kutta)
     813    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tsa_m      !< pointer: weighted tendency of sa for previous sub-timestep (Runge-Kutta)
     814    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tu_m       !< pointer: weighted tendency of u for previous sub-timestep (Runge-Kutta)
     815    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tv_m       !< pointer: weighted tendency of v for previous sub-timestep (Runge-Kutta)
     816    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  tw_m       !< pointer: weighted tendency of w for previous sub-timestep (Runge-Kutta)
     817    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u          !< pointer: horizontal velocity component u (x-direction)
     818    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  u_p        !< pointer: prognostic value of u
     819    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v          !< pointer: horizontal velocity component v (y-direction)
     820    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  v_p        !< pointer: prognostic value of v
     821    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  vpt        !< pointer: virtual potential temperature
     822    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w          !< pointer: vertical velocity component w (z-direction)
     823    REAL(wp), DIMENSION(:,:,:), POINTER, CONTIGUOUS ::  w_p        !< pointer: prognostic value of w
    820824#endif
    821825
     
    971975    CHARACTER (LEN=1)    ::  cycle_mg = 'w'                               !< namelist parameter (see documentation)
    972976    CHARACTER (LEN=1)    ::  timestep_reason = ' '                        !< 'A'dvection or 'D'iffusion criterion, written to RUN_CONTROL file
    973     CHARACTER (LEN=3)    ::  coupling_char = ''                           !< appended to filenames in coupled ocean-atmosphere runs ('_O': ocean PE, '_A': atmosphere PE)
     977    CHARACTER (LEN=8)    ::  coupling_char = ''                           !< appended to filenames in coupled or nested runs ('_O': ocean PE,
     978                                                                          !< '_NV': vertically nested atmosphere PE, '_N##': PE of nested domain ##
    974979    CHARACTER (LEN=8)    ::  most_method = 'newton'                       !< namelist parameter
    975980    CHARACTER (LEN=8)    ::  run_date                                     !< date of simulation run, printed to HEADER file
Note: See TracChangeset for help on using the changeset viewer.