Ignore:
Timestamp:
Mar 20, 2014 8:40:49 AM (10 years ago)
Author:
raasch
Message:

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

File:
1 edited

Legend:

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

    r1313 r1320  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! ONLY-attribute added to USE-statements,
     23! kind-parameters added to all INTEGER and REAL declaration statements,
     24! kinds are defined in new module kinds,
     25! old module precision_kind is removed,
     26! revision history before 2012 removed,
     27! comment fields (!:) to be used for variable explanations added to
     28! all variable declaration statements
    2329!
    2430! Former revisions:
     
    108114! 825 2012-02-19 03:03:44Z raasch
    109115! Output of cloud physics parameters/quantities complemented and restructured
    110 !
    111 ! 767 2011-10-14 06:39:12Z raasch
    112 ! Output of given initial u,v-profiles
    113 !
    114 ! 759 2011-09-15 13:58:31Z raasch
    115 ! output of maximum number of parallel io streams
    116 !
    117 ! 707 2011-03-29 11:39:40Z raasch
    118 ! bc_lr/ns replaced by bc_lr/ns_cyc
    119 !
    120 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    121 ! Output of advection scheme.
    122 ! Modified output of Prandtl-layer height.
    123 !
    124 ! 580 2010-10-05 13:59:11Z heinze
    125 ! Renaming of ws_vertical_gradient to subs_vertical_gradient,
    126 ! ws_vertical_gradient_level to subs_vertical_gradient_level and
    127 ! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
    128 !
    129 ! 493 2010-03-01 08:30:24Z raasch
    130 ! NetCDF data output format extendend for NetCDF4/HDF5
    131 !
    132 ! 449 2010-02-02 11:23:59Z raasch
    133 ! +large scale vertical motion (subsidence/ascent)
    134 ! Bugfix: index problem concerning gradient_level indices removed
    135 !
    136 ! 410 2009-12-04 17:05:40Z letzel
    137 ! Masked data output: + dt_domask, mask_01~20_x|y|z, mask_01~20_x|y|z_loop,
    138 ! mask_scale|_x|y|z, masks, skip_time_domask
    139 !
    140 ! 346 2009-07-06 10:13:41Z raasch
    141 ! initializing_actions='read_data_for_recycling' renamed to 'cyclic_fill'
    142 ! Coupling with independent precursor runs.
    143 ! Output of messages replaced by message handling routine.
    144 ! Output of several additional dvr parameters
    145 ! +canyon_height, canyon_width_x, canyon_width_y, canyon_wall_left,
    146 ! canyon_wall_south, conserve_volume_flow_mode, dp_external, dp_level_b,
    147 ! dp_smooth, dpdxy, u_bulk, v_bulk
    148 ! topography_grid_convention moved from user_header
    149 ! small bugfix concerning 3d 64bit netcdf output format
    150 !
    151 ! 206 2008-10-13 14:59:11Z raasch
    152 ! Bugfix: error in zu index in case of section_xy = -1
    153 !
    154 ! 198 2008-09-17 08:55:28Z raasch
    155 ! Format adjustments allowing output of larger revision numbers
    156 !
    157 ! 197 2008-09-16 15:29:03Z raasch
    158 ! allow 100 spectra levels instead of 10 for consistency with
    159 ! define_netcdf_header,
    160 ! bugfix in the output of the characteristic levels of potential temperature,
    161 ! geostrophic wind, scalar concentration, humidity and leaf area density,
    162 ! output of turbulence recycling informations
    163 !
    164 ! 138 2007-11-28 10:03:58Z letzel
    165 ! Allow new case bc_uv_t = 'dirichlet_0' for channel flow.
    166 ! Allow two instead of one digit to specify isosurface and slicer variables.
    167 ! Output of sorting frequency of particles
    168 !
    169 ! 108 2007-08-24 15:10:38Z letzel
    170 ! Output of informations for coupled model runs (boundary conditions etc.)
    171 ! + output of momentumfluxes at the top boundary
    172 ! Rayleigh damping for ocean, e_init
    173 !
    174 ! 97 2007-06-21 08:23:15Z raasch
    175 ! Adjustments for the ocean version.
    176 ! use_pt_reference renamed use_reference
    177 !
    178 ! 87 2007-05-22 15:46:47Z raasch
    179 ! Bugfix: output of use_upstream_for_tke
    180 !
    181 ! 82 2007-04-16 15:40:52Z raasch
    182 ! Preprocessor strings for different linux clusters changed to "lc",
    183 ! routine local_flush is used for buffer flushing
    184 !
    185 ! 76 2007-03-29 00:58:32Z raasch
    186 ! Output of netcdf_64bit_3d, particles-package is now part of the default code,
    187 ! output of the loop optimization method, moisture renamed humidity,
    188 ! output of subversion revision number
    189 !
    190 ! 19 2007-02-23 04:53:48Z raasch
    191 ! Output of scalar flux applied at top boundary
    192 !
    193 ! RCS Log replace by Id keyword, revision history cleaned up
    194 !
    195 ! Revision 1.63  2006/08/22 13:53:13  raasch
    196 ! Output of dz_max
    197116!
    198117! Revision 1.1  1997/08/11 06:17:20  raasch
     
    209128!-----------------------------------------------------------------------------!
    210129
    211     USE arrays_3d
     130    USE arrays_3d,                                                             &
     131        ONLY:  lad, pt_init, qsws, q_init, sa_init, shf, ug, vg, w_subs, zu
     132       
    212133    USE control_parameters
    213     USE cloud_parameters
    214     USE cpulog
    215     USE dvrp_variables
    216     USE grid_variables
    217     USE indices
    218     USE model_1d
    219     USE particle_attributes
     134       
     135    USE cloud_parameters,                                                      &
     136        ONLY:  cp, curvature_solution_effects, c_sedimentation,                &
     137               limiter_sedimentation, l_v, nc_const, r_d, ventilation_effect
     138       
     139    USE cpulog,                                                                &
     140        ONLY:  log_point_s
     141       
     142    USE dvrp_variables,                                                        &
     143        ONLY:  use_seperate_pe_for_dvrp_output
     144       
     145    USE grid_variables,                                                        &
     146        ONLY:  dx, dy
     147       
     148    USE indices,                                                               &
     149        ONLY:  mg_loc_ind, nnx, nny, nnz, nx, ny, nxl_mg, nxr_mg, nyn_mg,      &
     150               nys_mg, nzt, nzt_mg
     151       
     152    USE kinds
     153   
     154    USE model_1d,                                                              &
     155        ONLY:  damp_level_ind_1d, dt_pr_1d, dt_run_control_1d, end_time_1d
     156       
     157    USE particle_attributes,                                                   &
     158        ONLY:  bc_par_b, bc_par_lr, bc_par_ns, bc_par_t, collision_kernel,     &
     159               density_ratio, dissipation_classes, dt_min_part, dt_prel,       &
     160               dt_sort_particles, dt_write_particle_data, end_time_prel,       &
     161               maximum_number_of_tailpoints, maximum_tailpoint_age,            &
     162               minimum_tailpoint_distance, number_of_particle_groups,          &
     163               particle_advection, particle_advection_start,                   &
     164               particles_per_point, pdx, pdy, pdz,  psb, psl, psn, psr, pss,   &
     165               pst, radius, radius_classes, random_start_position,             &
     166               total_number_of_particles, use_particle_tails,                  &
     167               use_sgs_for_particles, total_number_of_tails,                   &
     168               vertical_particle_advection, write_particle_statistics
     169       
    220170    USE pegrid
    221     USE subsidence_mod
    222     USE spectrum
    223171
    224172    IMPLICIT NONE
    225173
    226     CHARACTER (LEN=1)  ::  prec
    227     CHARACTER (LEN=2)  ::  do2d_mode
    228     CHARACTER (LEN=5)  ::  section_chr
    229     CHARACTER (LEN=10) ::  coor_chr, host_chr
    230     CHARACTER (LEN=16) ::  begin_chr
    231     CHARACTER (LEN=26) ::  ver_rev
    232     CHARACTER (LEN=40) ::  output_format
    233     CHARACTER (LEN=70) ::  char1, char2, dopr_chr, &
    234                            do2d_xy, do2d_xz, do2d_yz, do3d_chr, &
    235                            domask_chr, run_classification
    236     CHARACTER (LEN=86) ::  coordinates, gradients, learde, slices,  &
    237                            temperatures, ugcomponent, vgcomponent
    238     CHARACTER (LEN=85) ::  roben, runten
    239 
    240     CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)
    241 
    242     INTEGER ::  av, bh, blx, bly, bxl, bxr, byn, bys, ch, count, cwx, cwy,  &
    243                 cxl, cxr, cyn, cys, dim, i, io, j, l, ll, mpi_type
    244     REAL    ::  cpuseconds_per_simulated_second
     174    CHARACTER (LEN=1)  ::  prec                !:
     175   
     176    CHARACTER (LEN=2)  ::  do2d_mode           !:
     177   
     178    CHARACTER (LEN=5)  ::  section_chr         !:
     179   
     180    CHARACTER (LEN=10) ::  coor_chr            !:
     181    CHARACTER (LEN=10) ::  host_chr            !:
     182   
     183    CHARACTER (LEN=16) ::  begin_chr           !:
     184   
     185    CHARACTER (LEN=26) ::  ver_rev             !:
     186   
     187    CHARACTER (LEN=40) ::  output_format       !:
     188   
     189    CHARACTER (LEN=70) ::  char1               !:
     190    CHARACTER (LEN=70) ::  char2               !:
     191    CHARACTER (LEN=70) ::  dopr_chr            !:
     192    CHARACTER (LEN=70) ::  do2d_xy             !:
     193    CHARACTER (LEN=70) ::  do2d_xz             !:
     194    CHARACTER (LEN=70) ::  do2d_yz             !:
     195    CHARACTER (LEN=70) ::  do3d_chr            !:
     196    CHARACTER (LEN=70) ::  domask_chr          !:
     197    CHARACTER (LEN=70) ::  run_classification  !:
     198   
     199    CHARACTER (LEN=85) ::  roben               !:
     200    CHARACTER (LEN=85) ::  runten              !:
     201   
     202    CHARACTER (LEN=86) ::  coordinates         !:
     203    CHARACTER (LEN=86) ::  gradients           !:
     204    CHARACTER (LEN=86) ::  learde              !:
     205    CHARACTER (LEN=86) ::  slices              !:
     206    CHARACTER (LEN=86) ::  temperatures        !:
     207    CHARACTER (LEN=86) ::  ugcomponent         !:
     208    CHARACTER (LEN=86) ::  vgcomponent         !:
     209
     210    CHARACTER (LEN=1), DIMENSION(1:3) ::  dir = (/ 'x', 'y', 'z' /)  !:
     211
     212    INTEGER(iwp) ::  av        !:
     213    INTEGER(iwp) ::  bh        !:
     214    INTEGER(iwp) ::  blx       !:
     215    INTEGER(iwp) ::  bly       !:
     216    INTEGER(iwp) ::  bxl       !:
     217    INTEGER(iwp) ::  bxr       !:
     218    INTEGER(iwp) ::  byn       !:
     219    INTEGER(iwp) ::  bys       !:
     220    INTEGER(iwp) ::  ch        !:
     221    INTEGER(iwp) ::  count     !:
     222    INTEGER(iwp) ::  cwx       !:
     223    INTEGER(iwp) ::  cwy       !:
     224    INTEGER(iwp) ::  cxl       !:
     225    INTEGER(iwp) ::  cxr       !:
     226    INTEGER(iwp) ::  cyn       !:
     227    INTEGER(iwp) ::  cys       !:
     228    INTEGER(iwp) ::  dim       !:
     229    INTEGER(iwp) ::  i         !:
     230    INTEGER(iwp) ::  io        !:
     231    INTEGER(iwp) ::  j         !:
     232    INTEGER(iwp) ::  l         !:
     233    INTEGER(iwp) ::  ll        !:
     234    INTEGER(iwp) ::  mpi_type  !:
     235   
     236    REAL(wp) ::  cpuseconds_per_simulated_second  !:
    245237
    246238!
Note: See TracChangeset for help on using the changeset viewer.