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

    r1310 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! revision history before 2012 removed,
     26! comment fields (!:) to be used for variable explanations added to
     27! all variable declaration statements
    2328!
    2429! Former revisions:
     
    5055! 807 2012-01-25 11:53:51Z maronga
    5156! New cpp directive "__check" implemented which is used by check_namelist_files
    52 !
    53 ! 771 2011-10-27 10:56:21Z heinze
    54 ! +lpt
    55 !
    56 ! 595 2010-11-12 09:52:10Z helmke
    57 ! Calculation of z locations for masked output changed
    58 !
    59 ! 564 2010-09-30 13:18:59Z helmke
    60 ! assignment of mask_xyz_loop added, palm message identifiers of masked output
    61 ! changed
    62 !/localdata/raasch.14299
    63 ! 557 2010-09-07 14:50:07Z weinreis
    64 ! bugfix message string in set_mask_locations
    65 !
    66 ! 553 2010-09-01 14:09:06Z weinreis
    67 ! parameters for masked output are replaced by arrays
    68 !
    69 ! 493 2010-03-01 08:30:24Z raasch
    70 ! netcdf_format_mask* and format_parallel_io replaced by netcdf_data_format
    7157!
    7258! 410 2009-12-04 17:05:40Z letzel
     
    7965!------------------------------------------------------------------------------!
    8066
    81     USE arrays_3d
    82     USE control_parameters
    83     USE grid_variables
    84     USE indices
    85     USE netcdf_control
    86     USE particle_attributes
     67    USE arrays_3d,                                                             &
     68        ONLY:  zu, zw
     69
     70    USE control_parameters,                                                    &
     71        ONLY:  constant_diffusion, cloud_droplets, cloud_physics,              &
     72               data_output_masks, data_output_masks_user,                      &
     73               doav, doav_n, domask, domask_no, dz, dz_stretch_level, humidity,&
     74               mask, masks, mask_scale, mask_i,                                &
     75               mask_i_global, mask_j, mask_j_global, mask_k, mask_k_global,    &
     76               mask_loop, mask_size, mask_size_l, mask_start_l, mask_x,        &
     77               mask_x_loop, mask_xyz_dimension, mask_y, mask_y_loop, mask_z,   &
     78               mask_z_loop, max_masks,  message_string, mid,                   &
     79               netcdf_data_format, passive_scalar, ocean
     80
     81    USE grid_variables,                                                        &
     82        ONLY:  dx, dy
     83
     84    USE indices,                                                               &
     85        ONLY:  nx, nxl, nxr, ny, nyn, nys, nz, nzb, nzt
     86
     87    USE kinds
     88
     89    USE netcdf_control,                                                        &
     90        ONLY:  domask_unit
     91
     92    USE particle_attributes,                                                   &
     93        ONLY:  particle_advection
     94
    8795    USE pegrid
    8896
    8997    IMPLICIT NONE
    9098
    91     CHARACTER (LEN=6)   ::  var
    92     CHARACTER (LEN=7)   ::  unit
    93     CHARACTER (LEN=10), DIMENSION(max_masks,100) ::  do_mask, do_mask_user
    94 
    95     INTEGER :: i, ilen, ind(6), ind_array(1), j, k, n, sender
    96     INTEGER, DIMENSION(:), ALLOCATABLE ::  tmp_array
    97 
    98     LOGICAL ::  found
     99    CHARACTER (LEN=6) ::  var  !:
     100    CHARACTER (LEN=7) ::  unit !:
     101   
     102    CHARACTER (LEN=10), DIMENSION(max_masks,100) ::  do_mask      !:
     103    CHARACTER (LEN=10), DIMENSION(max_masks,100) ::  do_mask_user !:
     104
     105    INTEGER(iwp) ::  i            !:
     106    INTEGER(iwp) ::  ilen         !:
     107    INTEGER(iwp) ::  ind(6)       !:
     108    INTEGER(iwp) ::  ind_array(1) !:
     109    INTEGER(iwp) ::  j            !:
     110    INTEGER(iwp) ::  k            !:
     111    INTEGER(iwp) ::  n            !:
     112    INTEGER(iwp) ::  sender       !:
     113   
     114    INTEGER(iwp), DIMENSION(:), ALLOCATABLE ::  tmp_array !:
     115
     116    LOGICAL ::  found !:
    99117!
    100118!-- Allocation and initialization
     
    480498       IMPLICIT NONE
    481499
    482        CHARACTER (LEN=2) :: dxyz_string, nxyz_string
    483        INTEGER  ::  count, count_l, dim, m, loop_begin, loop_end, loop_stride, &
    484                     lb, nxyz, ub
    485        REAL     ::  dxyz, ddxyz, tmp1, tmp2
     500       CHARACTER (LEN=2) ::  dxyz_string !:
     501       CHARACTER (LEN=2) ::  nxyz_string !:
     502       
     503       INTEGER(iwp)  ::  count       !:
     504       INTEGER(iwp)  ::  count_l     !:
     505       INTEGER(iwp)  ::  dim         !:
     506       INTEGER(iwp)  ::  m           !:
     507       INTEGER(iwp)  ::  loop_begin  !:
     508       INTEGER(iwp)  ::  loop_end    !:
     509       INTEGER(iwp)  ::  loop_stride !:
     510       INTEGER(iwp)  ::  lb          !:
     511       INTEGER(iwp)  ::  nxyz        !:
     512       INTEGER(iwp)  ::  ub          !:
     513       
     514       REAL(wp)      ::  dxyz  !:
     515       REAL(wp)      ::  ddxyz !:
     516       REAL(wp)      ::  tmp1  !:
     517       REAL(wp)      ::  tmp2  !:
    486518
    487519       count = 0;  count_l = 0;  ddxyz = 1.0 / dxyz;  tmp1 = 0.0;  tmp2 = 0.0
Note: See TracChangeset for help on using the changeset viewer.