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_dvrp.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! 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:
     
    2834! 1036 2012-10-22 13:43:42Z raasch
    2935! code put under GPL (PALM 3.9)
    30 !
    31 ! 284 2009-04-06 06:36:10Z raasch
    32 ! Definition of a colortable to be used for particles.
    33 ! Output names are changed: surface=groundplate, buildings=topography
    34 ! Output of messages replaced by message handling routine.
    35 ! Clipping implemented.
    36 ! Polygon reduction for building and ground plate isosurface. Reduction level
    37 ! for buildings can be chosen with parameter cluster_size.
    38 ! Steering, splitting, and rtsp routines not used on nec.
    39 ! ToDo: checking of mode_dvrp for legal values is not correct
    40 ! Implementation of a MPI-1 coupling: __mpi2 adjustments for MPI_COMM_WORLD
    41 !
    42 ! 210 2008-11-06 08:54:02Z raasch
    43 ! DVRP arguments changed to single precision, mode pathlines added
    44 !
    45 ! 155 2008-03-28 10:56:30Z letzel
    46 ! introduce prefix_chr to ensure unique dvrp_file path
    47 !
    48 ! 130 2007-11-13 14:08:40Z letzel
    49 ! allow two instead of one digit to specify isosurface and slicer variables
    50 ! Test output of isosurface on camera file
    51 !
    52 ! 82 2007-04-16 15:40:52Z raasch
    53 ! Preprocessor strings for different linux clusters changed to "lc",
    54 ! routine local_flush is used for buffer flushing
    55 !
    56 ! 17 2007-02-19 01:57:39Z raasch
    57 ! dvrp_output_local activated for all streams
    58 !
    59 ! 13 2007-02-14 12:15:07Z raasch
    60 ! RCS Log replace by Id keyword, revision history cleaned up
    61 !
    62 ! Revision 1.12  2006/02/23 12:30:22  raasch
    63 ! ebene renamed section, pl.. replaced by do..,
    6436!
    6537! Revision 1.1  2000/04/27 06:24:39  raasch
     
    7345#if defined( __dvrp_graphics )
    7446
    75     USE arrays_3d
     47    USE arrays_3d,                                                             &
     48        ONLY:  zu
     49       
    7650    USE DVRP
     51   
    7752    USE dvrp_variables
    78     USE grid_variables
    79     USE indices
     53   
     54    USE grid_variables,                                                        &
     55        ONLY:  dx, dy
     56       
     57    USE indices,                                                               &
     58        ONLY:  nx, nxl, nxr, ny, nyn, nys, nzb, nzb_s_inner
     59       
     60    USE kinds
     61   
    8062    USE pegrid
    81     USE control_parameters
     63   
     64    USE control_parameters,                                                               &
     65        ONLY:  message_string, nz_do3d, run_identifier, topography
    8266
    8367    IMPLICIT NONE
    8468
    85     CHARACTER (LEN=2)  ::  section_chr
    86     CHARACTER (LEN=3)  ::  prefix_chr
    87     CHARACTER (LEN=80) ::  dvrp_file_local
    88     INTEGER ::  cluster_mode, cluster_size_x, cluster_size_y, cluster_size_z, &
    89                 gradient_normals, i, j, k, l, m, nx_dvrp_l, nx_dvrp_r,        &
    90                 ny_dvrp_n, ny_dvrp_s, pn, tv, vn
    91     LOGICAL ::  allocated
    92     REAL(4) ::  center(3), cluster_alpha, distance, tmp_b, tmp_g, tmp_r, &
    93                 tmp_t, tmp_th, tmp_thr, tmp_x1, tmp_x2, tmp_y1, tmp_y2,  &
    94                 tmp_z1, tmp_z2, tmp_1, tmp_2, tmp_3, tmp_4, tmp_5, tmp_6, tmp_7
    95 
    96     REAL(4), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf
    97 
    98     TYPE(CSTRING), SAVE ::  dvrp_directory_c, dvrp_file_c, &
    99                             dvrp_file_local_c,dvrp_host_c, &
    100                             dvrp_password_c, dvrp_username_c, name_c
     69    CHARACTER (LEN=2)  ::  section_chr      !:
     70    CHARACTER (LEN=3)  ::  prefix_chr       !:
     71    CHARACTER (LEN=80) ::  dvrp_file_local  !:
     72   
     73    INTEGER(iwp) ::  cluster_mode      !:
     74    INTEGER(iwp) ::  cluster_size_x    !:
     75    INTEGER(iwp) ::  cluster_size_y    !:
     76    INTEGER(iwp) ::  cluster_size_z    !:
     77    INTEGER(iwp) ::  gradient_normals  !:
     78    INTEGER(iwp) ::  i                 !:
     79    INTEGER(iwp) ::  j                 !:
     80    INTEGER(iwp) ::  k                 !:
     81    INTEGER(iwp) ::  l                 !:
     82    INTEGER(iwp) ::  m                 !:
     83    INTEGER(iwp) ::  nx_dvrp_l         !:
     84    INTEGER(iwp) ::  nx_dvrp_r         !:
     85    INTEGER(iwp) ::  ny_dvrp_n         !:
     86    INTEGER(iwp) ::  ny_dvrp_s         !:
     87    INTEGER(iwp) ::  pn                !:
     88    INTEGER(iwp) ::  tv                !:
     89    INTEGER(iwp) ::  vn                !:
     90                     
     91    LOGICAL  ::  allocated  !:
     92   
     93    REAL(sp) ::  center(3)      !:
     94    REAL(sp) ::  cluster_alpha  !:
     95    REAL(sp) ::  distance       !:
     96    REAL(sp) ::  tmp_b          !:
     97    REAL(sp) ::  tmp_g          !:
     98    REAL(sp) ::  tmp_r          !:
     99    REAL(sp) ::  tmp_t          !:
     100    REAL(sp) ::  tmp_th         !:
     101    REAL(sp) ::  tmp_thr        !:
     102    REAL(sp) ::  tmp_x1         !:
     103    REAL(sp) ::  tmp_x2         !:
     104    REAL(sp) ::  tmp_y1         !:
     105    REAL(sp) ::  tmp_y2         !:
     106    REAL(sp) ::  tmp_z1         !:
     107    REAL(sp) ::  tmp_z2         !:
     108    REAL(sp) ::  tmp_1          !:
     109    REAL(sp) ::  tmp_2          !:
     110    REAL(sp) ::  tmp_3          !:
     111    REAL(sp) ::  tmp_4          !:
     112    REAL(sp) ::  tmp_5          !:
     113    REAL(sp) ::  tmp_6          !:
     114    REAL(sp) ::  tmp_7          !:
     115
     116    REAL(sp), DIMENSION(:,:,:), ALLOCATABLE ::  local_pf  !:
     117
     118    TYPE(CSTRING), SAVE ::  dvrp_directory_c   !:
     119    TYPE(CSTRING), SAVE ::  dvrp_file_c        !:
     120    TYPE(CSTRING), SAVE ::  dvrp_file_local_c  !:
     121    TYPE(CSTRING), SAVE ::  dvrp_host_c        !:
     122    TYPE(CSTRING), SAVE ::  dvrp_password_c    !:
     123    TYPE(CSTRING), SAVE ::  dvrp_username_c    !:
     124    TYPE(CSTRING), SAVE ::  name_c             !:
    101125
    102126!
     
    718742#if defined( __dvrp_graphics )
    719743
    720     USE control_parameters
    721     USE dvrp_variables
     744    USE dvrp_variables,                                                        &
     745        ONLY:  use_seperate_pe_for_dvrp_output
     746   
     747    USE kinds
     748   
    722749    USE pegrid
    723750
    724751    IMPLICIT NONE
    725752
    726     CHARACTER (LEN=4) ::  chr
    727     INTEGER           ::  idummy
     753    CHARACTER (LEN=4) ::  chr  !:
     754   
     755    INTEGER(iwp) ::  idummy    !:
    728756
    729757!
     
    778806!------------------------------------------------------------------------------!
    779807#if defined( __dvrp_graphics )
    780 
    781     USE control_parameters
    782     USE dvrp
    783     USE dvrp_variables
    784 
    785     INTEGER ::  m
     808                                               
     809    USE DVRP
     810   
     811    USE dvrp_variables,                                                        &
     812        ONLY: use_seperate_pe_for_dvrp_output
     813   
     814    USE kinds
     815
     816    INTEGER(iwp) ::  m  !:
    786817
    787818!
Note: See TracChangeset for help on using the changeset viewer.