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/diffusion_e.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:
     
    6066! 825 2012-02-19 03:03:44Z raasch
    6167! wang_collision_kernel renamed wang_kernel
    62 !
    63 ! 790 2011-11-29 03:11:20Z raasch
    64 ! diss is also calculated in case that the Wang kernel is used
    65 !
    66 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    67 ! nxl-1, nxr+1, nys-1, nyn+1 replaced by nxlg, nxrg, nysg, nyng
    68 !
    69 ! 97 2007-06-21 08:23:15Z raasch
    70 ! Adjustment of mixing length calculation for the ocean version. zw added to
    71 ! argument list.
    72 ! This is also a bugfix, because the height above the topography is now
    73 ! used instead of the height above level k=0.
    74 ! theta renamed var, dpt_dz renamed dvar_dz, +new argument var_reference
    75 ! use_pt_reference renamed use_reference
    76 !
    77 ! 65 2007-03-13 12:11:43Z raasch
    78 ! Reference temperature pt_reference can be used in buoyancy term
    79 !
    80 ! 20 2007-02-26 00:12:32Z raasch
    81 ! Bugfix: ddzw dimensioned 1:nzt"+1"
    82 ! Calculation extended for gridpoint nzt
    83 !
    84 ! RCS Log replace by Id keyword, revision history cleaned up
    85 !
    86 ! Revision 1.18  2006/08/04 14:29:43  raasch
    87 ! dissipation is stored in extra array diss if needed later on for calculating
    88 ! the sgs particle velocities
    8968!
    9069! Revision 1.1  1997/09/19 07:40:24  raasch
     
    11897    SUBROUTINE diffusion_e( var, var_reference )
    11998
    120        USE arrays_3d
    121        USE control_parameters
    122        USE grid_variables
    123        USE indices
    124        USE particle_attributes
     99       USE arrays_3d,                                                          &
     100           ONLY:  dd2zu, ddzu, ddzw, diss, e, km, l_grid, tend, zu, zw
     101           
     102       USE control_parameters,                                                 &
     103           ONLY:  atmos_ocean_sign, g, turbulence, use_single_reference_value, &
     104                  wall_adjustment, wall_adjustment_factor
     105                 
     106       USE grid_variables,                                                     &
     107           ONLY:  ddx2, ddy2
     108           
     109       USE indices,                                                            &
     110           ONLY:  nxl, nxr, nyn, nys, nzb, nzb_s_inner, nzt
     111           
     112       USE kinds
     113       
     114       USE particle_attributes,                                                &
     115           ONLY:  use_sgs_for_particles, wang_kernel
    125116
    126117       IMPLICIT NONE
    127118
    128        INTEGER ::  i, j, k
    129        REAL    ::  dvar_dz, l_stable, var_reference
     119       INTEGER(iwp) ::  i              !:
     120       INTEGER(iwp) ::  j              !:
     121       INTEGER(iwp) ::  k              !:
     122       REAL(wp)     ::  dvar_dz        !:
     123       REAL(wp)     ::  l_stable       !:
     124       REAL(wp)     ::  var_reference  !:
    130125
    131126#if defined( __nopointer )
    132        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
     127       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !:
    133128#else
    134        REAL, DIMENSION(:,:,:), POINTER ::  var
     129       REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !:
    135130#endif
    136        REAL, DIMENSION(nzb+1:nzt,nys:nyn) ::  dissipation, l, ll
     131       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  dissipation  !:
     132       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  l            !:
     133       REAL(wp), DIMENSION(nzb+1:nzt,nys:nyn) ::  ll           !:
    137134 
    138135
     
    304301    SUBROUTINE diffusion_e_acc( var, var_reference )
    305302
    306        USE arrays_3d
    307        USE control_parameters
    308        USE grid_variables
    309        USE indices
    310        USE particle_attributes
     303       USE arrays_3d,                                                          &
     304           ONLY:  dd2zu, ddzu, ddzw, diss, e, km, l_grid, tend, zu, zw
     305         
     306       USE control_parameters,                                                 &
     307           ONLY:  atmos_ocean_sign, g, turbulence, use_single_reference_value, &
     308                  wall_adjustment, wall_adjustment_factor
     309               
     310       USE grid_variables,                                                     &
     311           ONLY:  ddx2, ddy2
     312           
     313       USE indices,                                                            &
     314           ONLY:  i_left, i_right, j_north, j_south, nzb_s_inner, nzt
     315           
     316       USE kinds
     317       
     318       USE particle_attributes,                                                &
     319           ONLY:  use_sgs_for_particles, wang_kernel
    311320
    312321       IMPLICIT NONE
    313322
    314        INTEGER ::  i, j, k
    315        REAL    ::  dissipation, dvar_dz, l, ll, l_stable, var_reference
     323       INTEGER(iwp) ::  i              !:
     324       INTEGER(iwp) ::  j              !:
     325       INTEGER(iwp) ::  k              !:
     326       REAL(wp)     ::  dissipation    !:
     327       REAL(wp)     ::  dvar_dz        !:
     328       REAL(wp)     ::  l              !:
     329       REAL(wp)     ::  ll             !:
     330       REAL(wp)     ::  l_stable       !:
     331       REAL(wp)     ::  var_reference  !:
    316332
    317333#if defined( __nopointer )
    318        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
     334       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !:
    319335#else
    320        REAL, DIMENSION(:,:,:), POINTER ::  var
     336       REAL(wp), DIMENSION(:,:,:), POINTER ::  var  !:
    321337#endif
    322338
     
    481497    SUBROUTINE diffusion_e_ij( i, j, var, var_reference )
    482498
    483        USE arrays_3d
    484        USE control_parameters
    485        USE grid_variables
    486        USE indices
    487        USE particle_attributes
     499       USE arrays_3d,                                                          &
     500           ONLY:  dd2zu, ddzu, ddzw, diss, e, km, l_grid, tend, zu, zw
     501         
     502       USE control_parameters,                                                 &
     503           ONLY:  atmos_ocean_sign, g, turbulence, use_single_reference_value, &
     504                  wall_adjustment, wall_adjustment_factor
     505               
     506       USE grid_variables,                                                     &
     507           ONLY:  ddx2, ddy2
     508           
     509       USE indices,                                                            &
     510           ONLY:  nzb, nzb_s_inner, nzt
     511           
     512       USE kinds
     513       
     514       USE particle_attributes,                                                &
     515           ONLY:  use_sgs_for_particles, wang_kernel
    488516
    489517       IMPLICIT NONE
    490518
    491        INTEGER ::  i, j, k
    492        REAL    ::  dvar_dz, l_stable, var_reference
     519       INTEGER(iwp) ::  i              !:
     520       INTEGER(iwp) ::  j              !:
     521       INTEGER(iwp) ::  k              !:
     522       REAL(wp)     ::  dvar_dz        !:
     523       REAL(wp)     ::  l_stable       !:
     524       REAL(wp)     ::  var_reference  !:
    493525
    494526#if defined( __nopointer )
    495        REAL, DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var
     527       REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  var  !:
    496528#else
    497        REAL, DIMENSION(:,:,:), POINTER ::  var
     529       REAL(wp), DIMENSION(:,:,:), POINTER ::  var     !:
    498530#endif
    499        REAL, DIMENSION(nzb+1:nzt) ::  dissipation, l, ll
     531       REAL(wp), DIMENSION(nzb+1:nzt) ::  dissipation  !:
     532       REAL(wp), DIMENSION(nzb+1:nzt) ::  l            !:
     533       REAL(wp), DIMENSION(nzb+1:nzt) ::  ll           !:
    500534
    501535
Note: See TracChangeset for help on using the changeset viewer.