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

    r1319 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:
     
    4652! +z0h, z0h_av
    4753!
    48 ! 776 2011-10-31 08:02:51Z heinze
    49 ! bugfix: increase binary_version due to last commit
    50 !
    51 ! 771 2011-10-27 10:56:21Z heinze
    52 ! +lpt_av
    53 !
    54 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    55 ! +/- 1 replaced with +/- nbgp when swapping and allocating variables.
    56 ! Bugfix: When using initializing_actions = 'cyclic_fill' in some cases
    57 ! not the whole model domain was filled with data of the prerun.
    58 !
    59 ! 410 2009-12-04 17:05:40Z letzel
    60 ! format changed in test output from I2 to I4
    61 !
    62 ! 367 2009-08-25 08:35:52Z maronga
    63 ! Output of messages replaced by message handling routine.
    64 ! +shf_av, qsws_av
    65 !
    66 ! 220 2008-12-18 07:00:36Z raasch
    67 ! reading mechanism completely revised (subdomain/total domain size can vary
    68 ! arbitrarily between current and previous run)
    69 ! Bugfix: reading of spectrum_x|y from restart files ignored if total numbers
    70 ! of grid points do not match
    71 !
    72 ! 150 2008-02-29 08:19:58Z raasch
    73 ! Files from which restart data are to be read are determined and subsequently
    74 ! opened. The total domain on the restart file is allowed to be smaller than
    75 ! the current total domain. In this case it will be periodically mapped on the
    76 ! current domain (needed for recycling method).
    77 ! +call of user_read_restart_data, -dopr_time_count,
    78 ! hom_sum, volume_flow_area, volume_flow_initial moved to read_var_list,
    79 ! reading of old profil parameters (cross_..., dopr_crossindex, profile_***)
    80 ! removed, initialization of spectrum_x|y removed
    81 !
    82 ! 102 2007-07-27 09:09:17Z raasch
    83 ! +uswst, uswst_m, vswst, vswst_m
    84 !
    85 ! 96 2007-06-04 08:07:41Z raasch
    86 ! +rho_av, sa, sa_av, saswsb, saswst
    87 !
    88 ! 73 2007-03-20 08:33:14Z raasch
    89 ! +precipitation_amount, precipitation_rate_av, rif_wall, u_m_l, u_m_r, etc.,
    90 ! z0_av
    91 !
    92 ! 19 2007-02-23 04:53:48Z raasch
    93 ! +qswst, qswst_m, tswst, tswst_m
    94 !
    95 ! RCS Log replace by Id keyword, revision history cleaned up
    96 !
    97 ! Revision 1.4  2006/08/04 15:02:32  raasch
    98 ! +iran, iran_part
    99 !
    10054! Revision 1.1  2004/04/30 12:47:27  raasch
    10155! Initial revision
     
    10761!------------------------------------------------------------------------------!
    10862
    109     USE arrays_3d
     63    USE arrays_3d,                                                             &
     64        ONLY:  e, kh, km, p, pt, q, ql, qc, nr, nrs, nrsws, nrswst, qr, qrs,   &
     65               qrsws, qrswst, qs, qsws, qswst, sa, saswsb, saswst, rif,        &
     66               rif_wall, shf, ts, tswst, u, u_m_l, u_m_n, u_m_r, u_m_s, us,    &
     67               usws, uswst, v, v_m_l, v_m_n, v_m_r, v_m_s, vpt, vsws, vswst,   &
     68               w, w_m_l, w_m_n, w_m_r, w_m_s, z0, z0h
     69
    11070    USE averaging
    111     USE cloud_parameters
    112     USE control_parameters
    113     USE cpulog
    114     USE indices
    115     USE particle_attributes
     71
     72    USE cloud_parameters,                                                      &
     73        ONLY:  prr, precipitation_amount
     74
     75    USE control_parameters,                                                    &
     76        ONLY:  iran, humidity, passive_scalar, cloud_physics, cloud_droplets,  &
     77               icloud_scheme, message_string, outflow_l, outflow_n, outflow_r, &
     78               outflow_s, precipitation, ocean, topography
     79
     80    USE cpulog,                                                                &
     81        ONLY:  cpu_log, log_point_s
     82
     83    USE indices,                                                               &
     84        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nx_on_file, ny, nys, nysg, nyn, &
     85               nyng, ny_on_file, nzb, nzt
     86
     87    USE kinds
     88
     89    USE particle_attributes,                                                   &
     90        ONLY:  iran_part
     91
    11692    USE pegrid
    117     USE profil_parameter
    118     USE random_function_mod
    119     USE statistics
     93
     94    USE random_function_mod,                                                   &
     95        ONLY:  random_iv, random_iy
     96
     97    USE statistics,                                                            &
     98        ONLY:  spectrum_x, spectrum_y
     99
    120100
    121101    IMPLICIT NONE
    122102
    123103    CHARACTER (LEN=5)  ::  myid_char_save
    124     CHARACTER (LEN=10) ::  binary_version, version_on_file
     104    CHARACTER (LEN=10) ::  binary_version
     105    CHARACTER (LEN=10) ::  version_on_file
    125106    CHARACTER (LEN=20) ::  field_chr
    126107
    127     INTEGER ::  files_to_be_opened, i, j, k, myid_on_file,                    &
    128                 numprocs_on_file, nxlc, nxlf, nxlpr, nxl_on_file, nxrc, nxrf, &
    129                 nxrpr, nxr_on_file, nync, nynf, nynpr, nyn_on_file, nysc,     &
    130                 nysf, nyspr, nys_on_file, nzb_on_file, nzt_on_file, offset_x, &
    131                 offset_y, shift_x, shift_y
    132 
    133     INTEGER, DIMENSION(numprocs_previous_run) ::  file_list, overlap_count
    134 
    135     INTEGER, DIMENSION(numprocs_previous_run,1000) ::  nxlfa, nxrfa, nynfa, &
    136                                                        nysfa, offset_xa, &
    137                                                        offset_ya
    138     REAL ::  rdummy
    139 
    140     REAL, DIMENSION(:,:), ALLOCATABLE     ::  tmp_2d
    141     REAL, DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d, tmp_3dwul, tmp_3dwun,    &
    142                                               tmp_3dwur, tmp_3dwus, tmp_3dwvl, &
    143                                               tmp_3dwvn, tmp_3dwvr, tmp_3dwvs, &
    144                                               tmp_3dwwl, tmp_3dwwn, tmp_3dwwr, &
    145                                               tmp_3dwws
    146     REAL, DIMENSION(:,:,:,:), ALLOCATABLE ::  tmp_4d
     108    INTEGER(iwp) ::  files_to_be_opened  !:
     109    INTEGER(iwp) ::  i                   !:
     110    INTEGER(iwp) ::  j                   !:
     111    INTEGER(iwp) ::  k                   !:
     112    INTEGER(iwp) ::  myid_on_file        !:
     113    INTEGER(iwp) ::  numprocs_on_file    !:
     114    INTEGER(iwp) ::  nxlc                !:
     115    INTEGER(iwp) ::  nxlf                !:
     116    INTEGER(iwp) ::  nxlpr               !:
     117    INTEGER(iwp) ::  nxl_on_file         !:
     118    INTEGER(iwp) ::  nxrc                !:
     119    INTEGER(iwp) ::  nxrf                !:
     120    INTEGER(iwp) ::  nxrpr               !:
     121    INTEGER(iwp) ::  nxr_on_file         !:
     122    INTEGER(iwp) ::  nync                !:
     123    INTEGER(iwp) ::  nynf                !:
     124    INTEGER(iwp) ::  nynpr               !:
     125    INTEGER(iwp) ::  nyn_on_file         !:
     126    INTEGER(iwp) ::  nysc                !:
     127    INTEGER(iwp) ::  nysf                !:
     128    INTEGER(iwp) ::  nyspr               !:
     129    INTEGER(iwp) ::  nys_on_file         !:
     130    INTEGER(iwp) ::  nzb_on_file         !:
     131    INTEGER(iwp) ::  nzt_on_file         !:
     132    INTEGER(iwp) ::  offset_x            !:
     133    INTEGER(iwp) ::  offset_y            !:
     134    INTEGER(iwp) ::  shift_x             !:
     135    INTEGER(iwp) ::  shift_y             !:
     136
     137    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  file_list       !:
     138    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !:
     139
     140    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa      !:
     141    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa      !:
     142    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa      !:
     143    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa      !:
     144    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa  !:
     145    INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya  !:
     146
     147    REAL(wp) ::  rdummy
     148
     149    REAL(wp), DIMENSION(:,:), ALLOCATABLE     ::  tmp_2d     !:
     150    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3d     !:
     151    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwul  !:
     152    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwun  !:
     153    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwur  !:
     154    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwus  !:
     155    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvl  !:
     156    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvn  !:
     157    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvr  !:
     158    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwvs  !:
     159    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwl  !:
     160    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwn  !:
     161    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwwr  !:
     162    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   ::  tmp_3dwws  !:
     163
     164    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::  tmp_4d     !:
    147165
    148166
Note: See TracChangeset for help on using the changeset viewer.