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/netcdf.f90

    r1310 r1320  
    2323! Current revisions:
    2424! ------------------
    25 !
     25! ONLY-attribute added to USE-statements,
     26! kind-parameters added to all INTEGER and REAL declaration statements,
     27! kinds are defined in new module kinds,
     28! revision history before 2012 removed,
     29! comment fields (!:) to be used for variable explanations added to
     30! all variable declaration statements
    2631!
    2732! Former revisions:
     
    7075! cross_profiles, profile_rows, profile_columns are written to netCDF header
    7176!
    72 ! 771 2011-10-27 10:56:21Z heinze
    73 ! +lpt
    74 !
    75 ! 600 2010-11-24 16:10:51Z raasch
    76 ! bugfix concerning check of cross-section levels on netcdf-files to be
    77 ! extended (xz,yz)
    78 !
    79 ! 564 2010-09-30 13:18:59Z helmke
    80 ! nc_precision changed from 40 masks to 1 mask, start number of mask output
    81 ! files changed to 201, netcdf message identifiers of masked output changed
    82 !
    83 ! 519 2010-03-19 05:30:02Z raasch
    84 ! particle number defined as unlimited dimension in case of netCDF4 output,
    85 ! special characters like * and " are now allowed for netCDF variable names,
    86 ! replacement of these characters removed, routine clean_netcdf_varname
    87 ! removed
    88 !
    89 ! 493 2010-03-01 08:30:24Z raasch
    90 ! Extensions for netCDF4 output
    91 !
    92 ! 410 2009-12-04 17:05:40Z letzel
    93 ! masked data output
    94 !
    95 ! 359 2009-08-19 16:56:44Z letzel
    96 ! for extended netCDF files, the updated title attribute includes an update of
    97 ! time_average_text where appropriate.
    98 ! Bugfix for extended netCDF files: In order to avoid 'data mode' errors if
    99 ! updated attributes are larger than their original size, NF90_PUT_ATT is called
    100 ! in 'define mode' enclosed by NF90_REDEF and NF90_ENDDEF calls. This implies a
    101 ! possible performance loss; an alternative strategy would be to ensure equal
    102 ! attribute size in a job chain.
    103 ! netCDF unit attribute in timeseries output in case of statistic
    104 ! regions added.
    105 ! Output of netCDF messages with aid of message handling routine.
    106 ! Output of messages replaced by message handling routine.
    107 ! Typographical errors fixed.
    108 !
    109 ! 216 2008-11-25 07:12:43Z raasch
    110 ! Origin of the xy-coordinate system shifted from the center of the first
    111 ! grid cell (indices i=0, j=0) to the south-left corner of this cell.
    112 !
    113 ! 189 2008-08-13 17:09:26Z letzel
    114 ! consistently allow 100 spectra levels instead of 10
    115 ! bug fix in the determination of the number of output heights for spectra,
    116 ! +user-defined spectra
    117 !
    118 ! 97 2007-06-21 08:23:15Z raasch
    119 ! Grids defined for rho and sa
    120 !
    121 ! 48 2007-03-06 12:28:36Z raasch
    122 ! Output topography height information (zu_s_inner, zw_s_inner) to 2d-xy and 3d
    123 ! datasets
    124 !
    125 ! RCS Log replace by Id keyword, revision history cleaned up
    126 !
    127 ! Revision 1.12  2006/09/26 19:35:16  raasch
    128 ! Bugfix yv coordinates for yz cross sections
    129 !
    13077! Revision 1.1  2005/05/18 15:37:16  raasch
    13178! Initial revision
     
    14996#if defined( __netcdf )
    15097
    151     USE arrays_3d
    152     USE constants
    153     USE control_parameters
    154     USE grid_variables
    155     USE indices
     98    USE arrays_3d,                                                              &
     99        ONLY:  zu, zw
     100
     101    USE constants,                                                              &
     102        ONLY:  pi
     103
     104    USE control_parameters,                                                     &
     105        ONLY:  averaging_interval, averaging_interval_pr, averaging_interval_sp,&
     106        data_output_pr,  domask,  dopr_n,dopr_time_count, dopts_time_count,     &
     107        dots_time_count, dosp_time_count, do2d, do2d_xz_time_count, do3d,       &
     108        do2d_yz_time_count, mask_size, do2d_xy_time_count, do3d_time_count,     &
     109        domask_time_count, mask_i_global, mask_j_global,mask_k_global,          &
     110        message_string, mid, netcdf_data_format, netcdf_precision, ntdim_2d_xy, &
     111        ntdim_2d_xz, ntdim_2d_yz, ntdim_3d, nz_do3d, prt_time_count,            &
     112        run_description_header, section, simulated_time, topography
     113
     114    USE grid_variables,                                                         &
     115        ONLY:  dx, dy, zu_s_inner, zw_w_inner
     116
     117    USE indices,                                                                &
     118        ONLY:  nx, ny, nz ,nzb, nzt
     119
    156120    USE netcdf_control
     121
     122    USE kinds
     123
    157124    USE pegrid
    158     USE particle_attributes
    159     USE profil_parameter
    160     USE spectrum
    161     USE statistics
     125
     126    USE particle_attributes,                                                    &
     127        ONLY:  maximum_number_of_particles, number_of_particle_groups
     128
     129    USE profil_parameter,                                                       &
     130        ONLY:  crmax, cross_profiles, dopr_index,profile_columns, profile_rows
     131
     132    USE spectrum,                                                               &
     133        ONLY:  comp_spectra_level, data_output_sp, spectra_direction
     134
     135    USE statistics,                                                             &
     136        ONLY:  hom, statistic_regions
    162137
    163138
    164139    IMPLICIT NONE
    165140
    166     CHARACTER (LEN=2)              ::  suffix
    167     CHARACTER (LEN=2), INTENT (IN) ::  callmode
    168     CHARACTER (LEN=3)              ::  suffix1
    169     CHARACTER (LEN=4)              ::  grid_x, grid_y, grid_z
    170     CHARACTER (LEN=6)              ::  mode
    171     CHARACTER (LEN=10)             ::  netcdf_var_name, precision, var
    172     CHARACTER (LEN=80)             ::  time_average_text
    173     CHARACTER (LEN=2000)           ::  char_cross_profiles, var_list, var_list_old
    174 
    175     CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_adj,   &
    176                                                 cross_profiles_char
    177 
    178     INTEGER ::  av, cross_profiles_count, cross_profiles_maxi, delim, &
    179                 delim_old, file_id, i, id_last, id_x, id_y, id_z, j,  &
    180                 k, kk, ns, ns_old, ntime_count, nz_old
    181 
    182     INTEGER, SAVE ::  oldmode
    183 
    184     INTEGER, DIMENSION(1) ::  id_dim_time_old, id_dim_x_yz_old,  &
    185                               id_dim_y_xz_old, id_dim_zu_sp_old, &
    186                               id_dim_zu_xy_old, id_dim_zu_3d_old, &
    187                               id_dim_zu_mask_old
    188 
    189     INTEGER, DIMENSION(1:crmax) ::  cross_profiles_numb
    190 
    191     LOGICAL ::  found
    192 
    193     LOGICAL, INTENT (INOUT) ::  extend
    194 
    195     LOGICAL, SAVE ::  init_netcdf = .FALSE.
    196 
    197     REAL, DIMENSION(1) ::  last_time_coordinate
    198 
    199     REAL, DIMENSION(:), ALLOCATABLE   ::  netcdf_data
    200     REAL, DIMENSION(:,:), ALLOCATABLE ::  netcdf_data_2d
     141    CHARACTER (LEN=2)              ::  suffix                !:
     142    CHARACTER (LEN=2), INTENT (IN) ::  callmode              !:
     143    CHARACTER (LEN=3)              ::  suffix1               !:
     144    CHARACTER (LEN=4)              ::  grid_x                !:
     145    CHARACTER (LEN=4)              ::  grid_y                !:
     146    CHARACTER (LEN=4)              ::  grid_z                !:
     147    CHARACTER (LEN=6)              ::  mode                  !:
     148    CHARACTER (LEN=10)             ::  netcdf_var_name       !:
     149    CHARACTER (LEN=10)             ::  precision             !:
     150    CHARACTER (LEN=10)             ::  var                   !:
     151    CHARACTER (LEN=80)             ::  time_average_text     !:
     152    CHARACTER (LEN=2000)           ::  char_cross_profiles   !:
     153    CHARACTER (LEN=2000)           ::  var_list              !:
     154    CHARACTER (LEN=2000)           ::  var_list_old          !:
     155
     156    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_adj   !:
     157    CHARACTER (LEN=100), DIMENSION(1:crmax) ::  cross_profiles_char  !:
     158
     159    INTEGER(iwp) ::  av                                      !:
     160    INTEGER(iwp) ::  cross_profiles_count                    !:
     161    INTEGER(iwp) ::  cross_profiles_maxi                     !:
     162    INTEGER(iwp) ::  delim                                   !:
     163    INTEGER(iwp) ::  delim_old                               !:
     164    INTEGER(iwp) ::  file_id                                 !:
     165    INTEGER(iwp) ::  i                                       !:
     166    INTEGER(iwp) ::  id_last                                 !:
     167    INTEGER(iwp) ::  id_x                                    !:
     168    INTEGER(iwp) ::  id_y                                    !:
     169    INTEGER(iwp) ::  id_z                                    !:
     170    INTEGER(iwp) ::  j                                       !:
     171    INTEGER(iwp) ::  k                                       !:
     172    INTEGER(iwp) ::  kk                                      !:
     173    INTEGER(iwp) ::  ns                                      !:
     174    INTEGER(iwp) ::  ns_old                                  !:
     175    INTEGER(iwp) ::  ntime_count                             !:
     176    INTEGER(iwp) ::  nz_old                                  !:
     177
     178    INTEGER(iwp), SAVE ::  oldmode                           !:
     179
     180    INTEGER(iwp), DIMENSION(1) ::  id_dim_time_old           !:
     181    INTEGER(iwp), DIMENSION(1) ::  id_dim_x_yz_old           !:
     182    INTEGER(iwp), DIMENSION(1) ::  id_dim_y_xz_old           !:
     183    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_sp_old          !:
     184    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_xy_old          !:
     185    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_3d_old          !:
     186    INTEGER(iwp), DIMENSION(1) ::  id_dim_zu_mask_old        !:
     187
     188
     189    INTEGER(iwp), DIMENSION(1:crmax) ::  cross_profiles_numb !:
     190
     191    LOGICAL ::  found                                        !:
     192
     193    LOGICAL, INTENT (INOUT) ::  extend                       !:
     194
     195    LOGICAL, SAVE ::  init_netcdf = .FALSE.                  !:
     196
     197    REAL(wp), DIMENSION(1) ::  last_time_coordinate          !:
     198
     199    REAL(wp), DIMENSION(:), ALLOCATABLE   ::  netcdf_data    !:
     200    REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  netcdf_data_2d !:
    201201
    202202!
     
    49694969    CHARACTER(LEN=*) ::  routine_name
    49704970
    4971     INTEGER ::  errno
     4971    INTEGER(iwp) ::  errno
    49724972
    49734973    IF ( nc_stat /= NF90_NOERR )  THEN
Note: See TracChangeset for help on using the changeset viewer.