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

    r1310 r1320  
    2020! Current revisions:
    2121! -----------------
     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
    2229!
    2330! Former revisions:
     
    2734! 1036 2012-10-22 13:43:42Z raasch
    2835! code put under GPL (PALM 3.9)
    29 !
    30 ! 671 2011-01-11 12:04:00Z heinze $
    31 ! bugfix: access to ddzu(nzt+2) which is not defined
    32 !
    33 ! 667 2010-12-23 12:06:00Z suehring
    34 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    35 !
    36 ! 580 2010-10-05 13:59:11Z heinze
    37 ! Renaming of ws_vertical_gradient to subs_vertical_gradient,
    38 ! ws_vertical_gradient_level to subs_vertical_gradient_level and
    39 ! ws_vertical_gradient_level_ind to subs_vertical_gradient_level_i
    4036!
    4137! Revision 3.7 2009-12-11 14:15:58Z heinze
     
    6864    SUBROUTINE init_w_subsidence
    6965
    70        USE arrays_3d
    71        USE control_parameters
    72        USE grid_variables
    73        USE indices
    74        USE pegrid
    75        USE statistics
     66       USE arrays_3d,                                                          &
     67           ONLY:  dzu, w_subs, zu
     68
     69       USE control_parameters,                                                 &
     70           ONLY:  message_string, ocean, subs_vertical_gradient,               &
     71                  subs_vertical_gradient_level, subs_vertical_gradient_level_i
     72
     73       USE indices,                                                            &
     74           ONLY:  nzb, nzt
     75
     76       USE kinds
    7677
    7778       IMPLICIT NONE
    7879
    79        INTEGER :: i, k
    80        REAL    :: gradient, ws_surface
     80       INTEGER(iwp) ::  i !:
     81       INTEGER(iwp) ::  k !:
     82
     83       REAL(wp)     ::  gradient   !:
     84       REAL(wp)     ::  ws_surface !:
    8185
    8286       IF ( .NOT. ALLOCATED( w_subs )) THEN
     
    132136    SUBROUTINE subsidence( tendency, var, var_init )
    133137
    134        USE arrays_3d
    135        USE control_parameters
    136        USE grid_variables
    137        USE indices
    138        USE pegrid
    139        USE statistics
     138       USE arrays_3d,                                                          &
     139           ONLY:  ddzu, w_subs
     140
     141       USE control_parameters,                                                 &
     142           ONLY:  dt_3d
     143
     144       USE indices,                                                            &
     145           ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzb_s_inner,&
     146                  nzt
     147
     148       USE kinds
    140149
    141150       IMPLICIT NONE
    142151 
    143        INTEGER :: i, j, k
    144 
    145        REAL :: tmp_grad
     152       INTEGER(iwp) ::  i !:
     153       INTEGER(iwp) ::  j !:
     154       INTEGER(iwp) ::  k !:
     155
     156       REAL(wp)     ::  tmp_grad !:
    146157   
    147        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: var, tendency
    148        REAL, DIMENSION(nzb:nzt+1) :: var_init, var_mod
     158       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !:
     159       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !:
     160       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !:
     161       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !:
    149162
    150163       var_mod = var_init
     
    208221 SUBROUTINE subsidence_ij( i, j, tendency, var, var_init )
    209222
    210        USE arrays_3d
    211        USE control_parameters
    212        USE grid_variables
    213        USE indices
    214        USE pegrid
    215        USE statistics
     223       USE arrays_3d,                                                          &
     224           ONLY:  ddzu, w_subs
     225
     226       USE control_parameters,                                                 &
     227           ONLY:  dt_3d
     228
     229       USE indices,                                                            &
     230           ONLY:  nxl, nxlg, nxrg, nyng, nys, nysg, nzb_s_inner, nzb, nzt
     231
     232       USE kinds
    216233
    217234       IMPLICIT NONE
    218235 
    219        INTEGER :: i, j, k
    220 
    221        REAL :: tmp_grad
     236       INTEGER(iwp) ::  i !:
     237       INTEGER(iwp) ::  j !:
     238       INTEGER(iwp) ::  k !:
     239
     240       REAL(wp)     ::  tmp_grad !:
    222241   
    223        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) :: var, tendency
    224        REAL, DIMENSION(nzb:nzt+1) :: var_init, var_mod
     242       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var      !:
     243       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  tendency !:
     244       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_init                     !:
     245       REAL(wp), DIMENSION(nzb:nzt+1) ::  var_mod                      !:
    225246
    226247       var_mod = var_init
Note: See TracChangeset for help on using the changeset viewer.