Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/microphysics.f90

    r1647 r1682  
    1  MODULE microphysics_mod
    2 
     1!> @file microphysics.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    7978! Description:
    8079! ------------
    81 ! Calculate cloud microphysics according to the two moment bulk
    82 ! scheme by Seifert and Beheng (2006).
    83 !------------------------------------------------------------------------------!
     80!> Calculate cloud microphysics according to the two moment bulk
     81!> scheme by Seifert and Beheng (2006).
     82!------------------------------------------------------------------------------!
     83 MODULE microphysics_mod
     84 
    8485
    8586    PRIVATE
     
    130131
    131132!------------------------------------------------------------------------------!
    132 ! Call for all grid points
     133! Description:
     134! ------------
     135!> Call for all grid points
    133136!------------------------------------------------------------------------------!
    134137    SUBROUTINE microphysics_control
     
    156159       IMPLICIT NONE
    157160
    158        INTEGER(iwp) ::  i                 !:
    159        INTEGER(iwp) ::  j                 !:
    160        INTEGER(iwp) ::  k                 !:
    161 
    162        REAL(wp)     ::  t_surface         !:
     161       INTEGER(iwp) ::  i                 !<
     162       INTEGER(iwp) ::  j                 !<
     163       INTEGER(iwp) ::  k                 !<
     164
     165       REAL(wp)     ::  t_surface         !<
    163166
    164167       IF ( large_scale_forcing  .AND.  lsf_surf ) THEN
     
    205208    END SUBROUTINE microphysics_control
    206209
     210!------------------------------------------------------------------------------!
     211! Description:
     212! ------------
     213!> Adjust number of raindrops to avoid nonlinear effects in sedimentation and
     214!> evaporation of rain drops due to too small or too big weights
     215!> of rain drops (Stevens and Seifert, 2008).
     216!------------------------------------------------------------------------------!
    207217    SUBROUTINE adjust_cloud
    208218
     
    223233       IMPLICIT NONE
    224234
    225        INTEGER(iwp) ::  i                 !:
    226        INTEGER(iwp) ::  j                 !:
    227        INTEGER(iwp) ::  k                 !:
     235       INTEGER(iwp) ::  i                 !<
     236       INTEGER(iwp) ::  j                 !<
     237       INTEGER(iwp) ::  k                 !<
    228238
    229239       CALL cpu_log( log_point_s(54), 'adjust_cloud', 'start' )
     
    236246                   nr(k,j,i) = 0.0_wp
    237247                ELSE
    238 !
    239 !--                Adjust number of raindrops to avoid nonlinear effects in
    240 !--                sedimentation and evaporation of rain drops due to too small
    241 !--                or too big weights of rain drops (Stevens and Seifert, 2008).
    242248                   IF ( nr(k,j,i) * xrmin > qr(k,j,i) * hyrho(k) )  THEN
    243249                      nr(k,j,i) = qr(k,j,i) * hyrho(k) / xrmin
     
    245251                      nr(k,j,i) = qr(k,j,i) * hyrho(k) / xrmax
    246252                   ENDIF
    247 
    248253                ENDIF
    249254             ENDDO
     
    256261
    257262
     263!------------------------------------------------------------------------------!
     264! Description:
     265! ------------
     266!> Autoconversion rate (Seifert and Beheng, 2006).
     267!------------------------------------------------------------------------------!
    258268    SUBROUTINE autoconversion
    259269
     
    282292       IMPLICIT NONE
    283293
    284        INTEGER(iwp) ::  i                 !:
    285        INTEGER(iwp) ::  j                 !:
    286        INTEGER(iwp) ::  k                 !:
    287 
    288        REAL(wp)     ::  alpha_cc          !:                   
    289        REAL(wp)     ::  autocon           !:
    290        REAL(wp)     ::  dissipation       !:
    291        REAL(wp)     ::  k_au              !:
    292        REAL(wp)     ::  l_mix             !:
    293        REAL(wp)     ::  nu_c              !:
    294        REAL(wp)     ::  phi_au            !:
    295        REAL(wp)     ::  r_cc              !:
    296        REAL(wp)     ::  rc                !:
    297        REAL(wp)     ::  re_lambda         !:
    298        REAL(wp)     ::  selfcoll          !:
    299        REAL(wp)     ::  sigma_cc          !:
    300        REAL(wp)     ::  tau_cloud         !:
    301        REAL(wp)     ::  xc                !:
     294       INTEGER(iwp) ::  i                 !<
     295       INTEGER(iwp) ::  j                 !<
     296       INTEGER(iwp) ::  k                 !<
     297
     298       REAL(wp)     ::  alpha_cc          !<                   
     299       REAL(wp)     ::  autocon           !<
     300       REAL(wp)     ::  dissipation       !<
     301       REAL(wp)     ::  k_au              !<
     302       REAL(wp)     ::  l_mix             !<
     303       REAL(wp)     ::  nu_c              !<
     304       REAL(wp)     ::  phi_au            !<
     305       REAL(wp)     ::  r_cc              !<
     306       REAL(wp)     ::  rc                !<
     307       REAL(wp)     ::  re_lambda         !<
     308       REAL(wp)     ::  selfcoll          !<
     309       REAL(wp)     ::  sigma_cc          !<
     310       REAL(wp)     ::  tau_cloud         !<
     311       REAL(wp)     ::  xc                !<
    302312
    303313       CALL cpu_log( log_point_s(55), 'autoconversion', 'start' )
     
    387397
    388398
     399!------------------------------------------------------------------------------!
     400! Description:
     401! ------------
     402!> Accretion rate (Seifert and Beheng, 2006).
     403!------------------------------------------------------------------------------!
    389404    SUBROUTINE accretion
    390405
     
    408423       IMPLICIT NONE
    409424
    410        INTEGER(iwp) ::  i                 !:
    411        INTEGER(iwp) ::  j                 !:
    412        INTEGER(iwp) ::  k                 !:
    413 
    414        REAL(wp)     ::  accr              !:
    415        REAL(wp)     ::  k_cr              !:
    416        REAL(wp)     ::  phi_ac            !:
    417        REAL(wp)     ::  tau_cloud         !:
    418        REAL(wp)     ::  xc                !:
     425       INTEGER(iwp) ::  i                 !<
     426       INTEGER(iwp) ::  j                 !<
     427       INTEGER(iwp) ::  k                 !<
     428
     429       REAL(wp)     ::  accr              !<
     430       REAL(wp)     ::  k_cr              !<
     431       REAL(wp)     ::  phi_ac            !<
     432       REAL(wp)     ::  tau_cloud         !<
     433       REAL(wp)     ::  xc                !<
    419434
    420435       CALL cpu_log( log_point_s(56), 'accretion', 'start' )
     
    464479
    465480
     481!------------------------------------------------------------------------------!
     482! Description:
     483! ------------
     484!> Collisional breakup rate (Seifert, 2008).
     485!------------------------------------------------------------------------------!
    466486    SUBROUTINE selfcollection_breakup
    467487
     
    485505       IMPLICIT NONE
    486506
    487        INTEGER(iwp) ::  i                 !:
    488        INTEGER(iwp) ::  j                 !:
    489        INTEGER(iwp) ::  k                 !:
    490 
    491        REAL(wp)     ::  breakup           !:
    492        REAL(wp)     ::  dr                !:
    493        REAL(wp)     ::  phi_br            !:
    494        REAL(wp)     ::  selfcoll          !:
     507       INTEGER(iwp) ::  i                 !<
     508       INTEGER(iwp) ::  j                 !<
     509       INTEGER(iwp) ::  k                 !<
     510
     511       REAL(wp)     ::  breakup           !<
     512       REAL(wp)     ::  dr                !<
     513       REAL(wp)     ::  phi_br            !<
     514       REAL(wp)     ::  selfcoll          !<
    495515
    496516       CALL cpu_log( log_point_s(57), 'selfcollection', 'start' )
     
    530550
    531551
     552!------------------------------------------------------------------------------!
     553! Description:
     554! ------------
     555!> Evaporation of precipitable water. Condensation is neglected for
     556!> precipitable water.
     557!------------------------------------------------------------------------------!
    532558    SUBROUTINE evaporation_rain
    533 
    534 !
    535 !--    Evaporation of precipitable water. Condensation is neglected for
    536 !--    precipitable water.
    537559
    538560       USE arrays_3d,                                                          &
     
    561583       IMPLICIT NONE
    562584
    563        INTEGER(iwp) ::  i                 !:
    564        INTEGER(iwp) ::  j                 !:
    565        INTEGER(iwp) ::  k                 !:
    566 
    567        REAL(wp)     ::  alpha             !:
    568        REAL(wp)     ::  dr                !:
    569        REAL(wp)     ::  e_s               !:
    570        REAL(wp)     ::  evap              !:
    571        REAL(wp)     ::  evap_nr           !:
    572        REAL(wp)     ::  f_vent            !:
    573        REAL(wp)     ::  g_evap            !:
    574        REAL(wp)     ::  lambda_r          !:
    575        REAL(wp)     ::  mu_r              !:
    576        REAL(wp)     ::  mu_r_2            !:
    577        REAL(wp)     ::  mu_r_5d2          !:
    578        REAL(wp)     ::  nr_0              !:
    579        REAL(wp)     ::  q_s               !:
    580        REAL(wp)     ::  sat               !:
    581        REAL(wp)     ::  t_l               !:
    582        REAL(wp)     ::  temp              !:
    583        REAL(wp)     ::  xr                !:
     585       INTEGER(iwp) ::  i                 !<
     586       INTEGER(iwp) ::  j                 !<
     587       INTEGER(iwp) ::  k                 !<
     588
     589       REAL(wp)     ::  alpha             !<
     590       REAL(wp)     ::  dr                !<
     591       REAL(wp)     ::  e_s               !<
     592       REAL(wp)     ::  evap              !<
     593       REAL(wp)     ::  evap_nr           !<
     594       REAL(wp)     ::  f_vent            !<
     595       REAL(wp)     ::  g_evap            !<
     596       REAL(wp)     ::  lambda_r          !<
     597       REAL(wp)     ::  mu_r              !<
     598       REAL(wp)     ::  mu_r_2            !<
     599       REAL(wp)     ::  mu_r_5d2          !<
     600       REAL(wp)     ::  nr_0              !<
     601       REAL(wp)     ::  q_s               !<
     602       REAL(wp)     ::  sat               !<
     603       REAL(wp)     ::  t_l               !<
     604       REAL(wp)     ::  temp              !<
     605       REAL(wp)     ::  xr                !<
    584606
    585607       CALL cpu_log( log_point_s(58), 'evaporation', 'start' )
     
    690712
    691713
     714!------------------------------------------------------------------------------!
     715! Description:
     716! ------------
     717!> Sedimentation of cloud droplets (Ackermann et al., 2009, MWR).
     718!------------------------------------------------------------------------------!
    692719    SUBROUTINE sedimentation_cloud
    693720
     
    714741       IMPLICIT NONE
    715742
    716        INTEGER(iwp) ::  i                 !:
    717        INTEGER(iwp) ::  j                 !:
    718        INTEGER(iwp) ::  k                 !:
    719 
    720        REAL(wp), DIMENSION(nzb:nzt+1) :: sed_qc !:
     743       INTEGER(iwp) ::  i                 !<
     744       INTEGER(iwp) ::  j                 !<
     745       INTEGER(iwp) ::  k                 !<
     746
     747       REAL(wp), DIMENSION(nzb:nzt+1) :: sed_qc !<
    721748
    722749       CALL cpu_log( log_point_s(59), 'sed_cloud', 'start' )
    723750
    724 !
    725 !--    Sedimentation of cloud droplets (Ackermann et al., 2009, MWR):
    726751       sed_qc(nzt+1) = 0.0_wp
    727752
     
    758783
    759784
     785!------------------------------------------------------------------------------!
     786! Description:
     787! ------------
     788!> Computation of sedimentation flux. Implementation according to Stevens
     789!> and Seifert (2008). Code is based on UCLA-LES.
     790!------------------------------------------------------------------------------!
    760791    SUBROUTINE sedimentation_rain
    761792
     
    787818       IMPLICIT NONE
    788819
    789        INTEGER(iwp) ::  i                          !:
    790        INTEGER(iwp) ::  j                          !:
    791        INTEGER(iwp) ::  k                          !:
    792        INTEGER(iwp) ::  k_run                      !:
    793 
    794        REAL(wp)     ::  c_run                      !:
    795        REAL(wp)     ::  d_max                      !:
    796        REAL(wp)     ::  d_mean                     !:
    797        REAL(wp)     ::  d_min                      !:
    798        REAL(wp)     ::  dr                         !:
    799        REAL(wp)     ::  dt_sedi                    !:
    800        REAL(wp)     ::  flux                       !:
    801        REAL(wp)     ::  lambda_r                   !:
    802        REAL(wp)     ::  mu_r                       !:
    803        REAL(wp)     ::  z_run                      !:
    804 
    805        REAL(wp), DIMENSION(nzb:nzt+1) ::  c_nr     !:
    806        REAL(wp), DIMENSION(nzb:nzt+1) ::  c_qr     !:
    807        REAL(wp), DIMENSION(nzb:nzt+1) ::  d_nr     !:
    808        REAL(wp), DIMENSION(nzb:nzt+1) ::  d_qr     !:
    809        REAL(wp), DIMENSION(nzb:nzt+1) ::  nr_slope !:
    810        REAL(wp), DIMENSION(nzb:nzt+1) ::  qr_slope !:
    811        REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_nr   !:
    812        REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_qr   !:
    813        REAL(wp), DIMENSION(nzb:nzt+1) ::  w_nr     !:
    814        REAL(wp), DIMENSION(nzb:nzt+1) ::  w_qr     !:
     820       INTEGER(iwp) ::  i                          !<
     821       INTEGER(iwp) ::  j                          !<
     822       INTEGER(iwp) ::  k                          !<
     823       INTEGER(iwp) ::  k_run                      !<
     824
     825       REAL(wp)     ::  c_run                      !<
     826       REAL(wp)     ::  d_max                      !<
     827       REAL(wp)     ::  d_mean                     !<
     828       REAL(wp)     ::  d_min                      !<
     829       REAL(wp)     ::  dr                         !<
     830       REAL(wp)     ::  dt_sedi                    !<
     831       REAL(wp)     ::  flux                       !<
     832       REAL(wp)     ::  lambda_r                   !<
     833       REAL(wp)     ::  mu_r                       !<
     834       REAL(wp)     ::  z_run                      !<
     835
     836       REAL(wp), DIMENSION(nzb:nzt+1) ::  c_nr     !<
     837       REAL(wp), DIMENSION(nzb:nzt+1) ::  c_qr     !<
     838       REAL(wp), DIMENSION(nzb:nzt+1) ::  d_nr     !<
     839       REAL(wp), DIMENSION(nzb:nzt+1) ::  d_qr     !<
     840       REAL(wp), DIMENSION(nzb:nzt+1) ::  nr_slope !<
     841       REAL(wp), DIMENSION(nzb:nzt+1) ::  qr_slope !<
     842       REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_nr   !<
     843       REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_qr   !<
     844       REAL(wp), DIMENSION(nzb:nzt+1) ::  w_nr     !<
     845       REAL(wp), DIMENSION(nzb:nzt+1) ::  w_qr     !<
    815846
    816847       CALL cpu_log( log_point_s(60), 'sed_rain', 'start' )
    817 !
    818 !--    Computation of sedimentation flux. Implementation according to Stevens
    819 !--    and Seifert (2008). Code is based on UCLA-LES.
     848
    820849       IF ( intermediate_timestep_count == 1 )  prr(:,:,:) = 0.0_wp
    821850!
     
    10031032
    10041033!------------------------------------------------------------------------------!
    1005 ! Call for grid point i,j
     1034! Description:
     1035! ------------
     1036!> Call for grid point i,j
    10061037!------------------------------------------------------------------------------!
    10071038
     
    10311062       IMPLICIT NONE
    10321063
    1033        INTEGER(iwp) ::  i                 !:
    1034        INTEGER(iwp) ::  j                 !:
    1035        INTEGER(iwp) ::  k                 !:
    1036 
    1037        REAL(wp)     ::  t_surface         !:
     1064       INTEGER(iwp) ::  i                 !<
     1065       INTEGER(iwp) ::  j                 !<
     1066       INTEGER(iwp) ::  k                 !<
     1067
     1068       REAL(wp)     ::  t_surface         !<
    10381069
    10391070       IF ( large_scale_forcing  .AND.  lsf_surf ) THEN
     
    10991130    END SUBROUTINE microphysics_control_ij
    11001131
     1132!------------------------------------------------------------------------------!
     1133! Description:
     1134! ------------
     1135!> Adjust number of raindrops to avoid nonlinear effects in
     1136!> sedimentation and evaporation of rain drops due to too small or
     1137!> too big weights of rain drops (Stevens and Seifert, 2008).
     1138!> The same procedure is applied to cloud droplets if they are determined
     1139!> prognostically. Call for grid point i,j
     1140!------------------------------------------------------------------------------!
    11011141    SUBROUTINE adjust_cloud_ij( i, j )
    11021142
     
    11141154       IMPLICIT NONE
    11151155
    1116        INTEGER(iwp) ::  i                 !:
    1117        INTEGER(iwp) ::  j                 !:
    1118        INTEGER(iwp) ::  k                 !:
    1119 !
    1120 !--    Adjust number of raindrops to avoid nonlinear effects in
    1121 !--    sedimentation and evaporation of rain drops due to too small or
    1122 !--    too big weights of rain drops (Stevens and Seifert, 2008).
    1123 !--    The same procedure is applied to cloud droplets if they are determined
    1124 !--    prognostically. 
     1156       INTEGER(iwp) ::  i                 !<
     1157       INTEGER(iwp) ::  j                 !<
     1158       INTEGER(iwp) ::  k                 !<
     1159
    11251160       DO  k = nzb_s_inner(j,i)+1, nzt
    11261161
     
    11461181
    11471182
     1183!------------------------------------------------------------------------------!
     1184! Description:
     1185! ------------
     1186!> Autoconversion rate (Seifert and Beheng, 2006). Call for grid point i,j
     1187!------------------------------------------------------------------------------!
    11481188    SUBROUTINE autoconversion_ij( i, j )
    11491189
     
    11681208       IMPLICIT NONE
    11691209
    1170        INTEGER(iwp) ::  i                 !:
    1171        INTEGER(iwp) ::  j                 !:
    1172        INTEGER(iwp) ::  k                 !:
    1173 
    1174        REAL(wp)     ::  alpha_cc          !:                   
    1175        REAL(wp)     ::  autocon           !:
    1176        REAL(wp)     ::  dissipation       !:
    1177        REAL(wp)     ::  k_au              !:
    1178        REAL(wp)     ::  l_mix             !:
    1179        REAL(wp)     ::  nu_c              !:
    1180        REAL(wp)     ::  phi_au            !:
    1181        REAL(wp)     ::  r_cc              !:
    1182        REAL(wp)     ::  rc                !:
    1183        REAL(wp)     ::  re_lambda         !:
    1184        REAL(wp)     ::  selfcoll          !:
    1185        REAL(wp)     ::  sigma_cc          !:
    1186        REAL(wp)     ::  tau_cloud         !:
    1187        REAL(wp)     ::  xc                !:
     1210       INTEGER(iwp) ::  i                 !<
     1211       INTEGER(iwp) ::  j                 !<
     1212       INTEGER(iwp) ::  k                 !<
     1213
     1214       REAL(wp)     ::  alpha_cc          !<                   
     1215       REAL(wp)     ::  autocon           !<
     1216       REAL(wp)     ::  dissipation       !<
     1217       REAL(wp)     ::  k_au              !<
     1218       REAL(wp)     ::  l_mix             !<
     1219       REAL(wp)     ::  nu_c              !<
     1220       REAL(wp)     ::  phi_au            !<
     1221       REAL(wp)     ::  r_cc              !<
     1222       REAL(wp)     ::  rc                !<
     1223       REAL(wp)     ::  re_lambda         !<
     1224       REAL(wp)     ::  selfcoll          !<
     1225       REAL(wp)     ::  sigma_cc          !<
     1226       REAL(wp)     ::  tau_cloud         !<
     1227       REAL(wp)     ::  xc                !<
    11881228
    11891229       DO  k = nzb_s_inner(j,i)+1, nzt
     
    12621302
    12631303
     1304!------------------------------------------------------------------------------!
     1305! Description:
     1306! ------------
     1307!> Accretion rate (Seifert and Beheng, 2006). Call for grid point i,j
     1308!------------------------------------------------------------------------------!
    12641309    SUBROUTINE accretion_ij( i, j )
    12651310
     
    12801325       IMPLICIT NONE
    12811326
    1282        INTEGER(iwp) ::  i                 !:
    1283        INTEGER(iwp) ::  j                 !:
    1284        INTEGER(iwp) ::  k                 !:
    1285 
    1286        REAL(wp)     ::  accr              !:
    1287        REAL(wp)     ::  k_cr              !:
    1288        REAL(wp)     ::  phi_ac            !:
    1289        REAL(wp)     ::  tau_cloud         !:
    1290        REAL(wp)     ::  xc                !:
     1327       INTEGER(iwp) ::  i                 !<
     1328       INTEGER(iwp) ::  j                 !<
     1329       INTEGER(iwp) ::  k                 !<
     1330
     1331       REAL(wp)     ::  accr              !<
     1332       REAL(wp)     ::  k_cr              !<
     1333       REAL(wp)     ::  phi_ac            !<
     1334       REAL(wp)     ::  tau_cloud         !<
     1335       REAL(wp)     ::  xc                !<
    12911336
    12921337       DO  k = nzb_s_inner(j,i)+1, nzt
     
    13261371
    13271372
     1373!------------------------------------------------------------------------------!
     1374! Description:
     1375! ------------
     1376!> Collisional breakup rate (Seifert, 2008). Call for grid point i,j
     1377!------------------------------------------------------------------------------!
    13281378    SUBROUTINE selfcollection_breakup_ij( i, j )
    13291379
     
    13441394       IMPLICIT NONE
    13451395
    1346        INTEGER(iwp) ::  i                 !:
    1347        INTEGER(iwp) ::  j                 !:
    1348        INTEGER(iwp) ::  k                 !:
    1349 
    1350        REAL(wp)     ::  breakup           !:
    1351        REAL(wp)     ::  dr                !:
    1352        REAL(wp)     ::  phi_br            !:
    1353        REAL(wp)     ::  selfcoll          !:
     1396       INTEGER(iwp) ::  i                 !<
     1397       INTEGER(iwp) ::  j                 !<
     1398       INTEGER(iwp) ::  k                 !<
     1399
     1400       REAL(wp)     ::  breakup           !<
     1401       REAL(wp)     ::  dr                !<
     1402       REAL(wp)     ::  phi_br            !<
     1403       REAL(wp)     ::  selfcoll          !<
    13541404
    13551405       DO  k = nzb_s_inner(j,i)+1, nzt
     
    13791429
    13801430
     1431!------------------------------------------------------------------------------!
     1432! Description:
     1433! ------------
     1434!> Evaporation of precipitable water. Condensation is neglected for
     1435!> precipitable water. Call for grid point i,j
     1436!------------------------------------------------------------------------------!
    13811437    SUBROUTINE evaporation_rain_ij( i, j )
    1382 !
    1383 !--    Evaporation of precipitable water. Condensation is neglected for
    1384 !--    precipitable water.
    13851438
    13861439       USE arrays_3d,                                                          &
     
    14061459       IMPLICIT NONE
    14071460
    1408        INTEGER(iwp) ::  i                 !:
    1409        INTEGER(iwp) ::  j                 !:
    1410        INTEGER(iwp) ::  k                 !:
    1411 
    1412        REAL(wp)     ::  alpha             !:
    1413        REAL(wp)     ::  dr                !:
    1414        REAL(wp)     ::  e_s               !:
    1415        REAL(wp)     ::  evap              !:
    1416        REAL(wp)     ::  evap_nr           !:
    1417        REAL(wp)     ::  f_vent            !:
    1418        REAL(wp)     ::  g_evap            !:
    1419        REAL(wp)     ::  lambda_r          !:
    1420        REAL(wp)     ::  mu_r              !:
    1421        REAL(wp)     ::  mu_r_2            !:
    1422        REAL(wp)     ::  mu_r_5d2          !:
    1423        REAL(wp)     ::  nr_0              !:
    1424        REAL(wp)     ::  q_s               !:
    1425        REAL(wp)     ::  sat               !:
    1426        REAL(wp)     ::  t_l               !:
    1427        REAL(wp)     ::  temp              !:
    1428        REAL(wp)     ::  xr                !:
     1461       INTEGER(iwp) ::  i                 !<
     1462       INTEGER(iwp) ::  j                 !<
     1463       INTEGER(iwp) ::  k                 !<
     1464
     1465       REAL(wp)     ::  alpha             !<
     1466       REAL(wp)     ::  dr                !<
     1467       REAL(wp)     ::  e_s               !<
     1468       REAL(wp)     ::  evap              !<
     1469       REAL(wp)     ::  evap_nr           !<
     1470       REAL(wp)     ::  f_vent            !<
     1471       REAL(wp)     ::  g_evap            !<
     1472       REAL(wp)     ::  lambda_r          !<
     1473       REAL(wp)     ::  mu_r              !<
     1474       REAL(wp)     ::  mu_r_2            !<
     1475       REAL(wp)     ::  mu_r_5d2          !<
     1476       REAL(wp)     ::  nr_0              !<
     1477       REAL(wp)     ::  q_s               !<
     1478       REAL(wp)     ::  sat               !<
     1479       REAL(wp)     ::  t_l               !<
     1480       REAL(wp)     ::  temp              !<
     1481       REAL(wp)     ::  xr                !<
    14291482
    14301483       DO  k = nzb_s_inner(j,i)+1, nzt
     
    15231576
    15241577
     1578!------------------------------------------------------------------------------!
     1579! Description:
     1580! ------------
     1581!> Sedimentation of cloud droplets (Ackermann et al., 2009, MWR).
     1582!> Call for grid point i,j
     1583!------------------------------------------------------------------------------!
    15251584    SUBROUTINE sedimentation_cloud_ij( i, j )
    15261585
     
    15441603       IMPLICIT NONE
    15451604
    1546        INTEGER(iwp) ::  i                 !:
    1547        INTEGER(iwp) ::  j                 !:
    1548        INTEGER(iwp) ::  k                 !:
    1549 
    1550        REAL(wp), DIMENSION(nzb:nzt+1) :: sed_qc  !:
    1551 
    1552 !
    1553 !--    Sedimentation of cloud droplets (Ackermann et al., 2009, MWR):
     1605       INTEGER(iwp) ::  i                 !<
     1606       INTEGER(iwp) ::  j                 !<
     1607       INTEGER(iwp) ::  k                 !<
     1608
     1609       REAL(wp), DIMENSION(nzb:nzt+1) :: sed_qc  !<
     1610
    15541611       sed_qc(nzt+1) = 0.0_wp
    15551612
     
    15781635
    15791636
     1637!------------------------------------------------------------------------------!
     1638! Description:
     1639! ------------
     1640!> Computation of sedimentation flux. Implementation according to Stevens
     1641!> and Seifert (2008). Code is based on UCLA-LES. Call for grid point i,j
     1642!------------------------------------------------------------------------------!
    15801643    SUBROUTINE sedimentation_rain_ij( i, j )
    15811644
     
    16041667       IMPLICIT NONE
    16051668
    1606        INTEGER(iwp) ::  i                          !:
    1607        INTEGER(iwp) ::  j                          !:
    1608        INTEGER(iwp) ::  k                          !:
    1609        INTEGER(iwp) ::  k_run                      !:
    1610 
    1611        REAL(wp)     ::  c_run                      !:
    1612        REAL(wp)     ::  d_max                      !:
    1613        REAL(wp)     ::  d_mean                     !:
    1614        REAL(wp)     ::  d_min                      !:
    1615        REAL(wp)     ::  dr                         !:
    1616        REAL(wp)     ::  dt_sedi                    !:
    1617        REAL(wp)     ::  flux                       !:
    1618        REAL(wp)     ::  lambda_r                   !:
    1619        REAL(wp)     ::  mu_r                       !:
    1620        REAL(wp)     ::  z_run                      !:
    1621 
    1622        REAL(wp), DIMENSION(nzb:nzt+1) ::  c_nr     !:
    1623        REAL(wp), DIMENSION(nzb:nzt+1) ::  c_qr     !:
    1624        REAL(wp), DIMENSION(nzb:nzt+1) ::  d_nr     !:
    1625        REAL(wp), DIMENSION(nzb:nzt+1) ::  d_qr     !:
    1626        REAL(wp), DIMENSION(nzb:nzt+1) ::  nr_slope !:
    1627        REAL(wp), DIMENSION(nzb:nzt+1) ::  qr_slope !:
    1628        REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_nr   !:
    1629        REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_qr   !:
    1630        REAL(wp), DIMENSION(nzb:nzt+1) ::  w_nr     !:
    1631        REAL(wp), DIMENSION(nzb:nzt+1) ::  w_qr     !:
    1632 
    1633 
    1634 !
    1635 !--    Computation of sedimentation flux. Implementation according to Stevens
    1636 !--    and Seifert (2008). Code is based on UCLA-LES.
     1669       INTEGER(iwp) ::  i                          !<
     1670       INTEGER(iwp) ::  j                          !<
     1671       INTEGER(iwp) ::  k                          !<
     1672       INTEGER(iwp) ::  k_run                      !<
     1673
     1674       REAL(wp)     ::  c_run                      !<
     1675       REAL(wp)     ::  d_max                      !<
     1676       REAL(wp)     ::  d_mean                     !<
     1677       REAL(wp)     ::  d_min                      !<
     1678       REAL(wp)     ::  dr                         !<
     1679       REAL(wp)     ::  dt_sedi                    !<
     1680       REAL(wp)     ::  flux                       !<
     1681       REAL(wp)     ::  lambda_r                   !<
     1682       REAL(wp)     ::  mu_r                       !<
     1683       REAL(wp)     ::  z_run                      !<
     1684
     1685       REAL(wp), DIMENSION(nzb:nzt+1) ::  c_nr     !<
     1686       REAL(wp), DIMENSION(nzb:nzt+1) ::  c_qr     !<
     1687       REAL(wp), DIMENSION(nzb:nzt+1) ::  d_nr     !<
     1688       REAL(wp), DIMENSION(nzb:nzt+1) ::  d_qr     !<
     1689       REAL(wp), DIMENSION(nzb:nzt+1) ::  nr_slope !<
     1690       REAL(wp), DIMENSION(nzb:nzt+1) ::  qr_slope !<
     1691       REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_nr   !<
     1692       REAL(wp), DIMENSION(nzb:nzt+1) ::  sed_qr   !<
     1693       REAL(wp), DIMENSION(nzb:nzt+1) ::  w_nr     !<
     1694       REAL(wp), DIMENSION(nzb:nzt+1) ::  w_qr     !<
     1695
    16371696       IF ( intermediate_timestep_count == 1 )  prr(:,j,i) = 0.0_wp
    16381697!
     
    17961855    END SUBROUTINE sedimentation_rain_ij
    17971856
    1798 !------------------------------------------------------------------------------!
    1799 ! Call for all optimizations
    1800 !------------------------------------------------------------------------------!
    1801 !
    1802 !-- This function computes the gamma function (Press et al., 1992).
    1803 !-- The gamma function is needed for the calculation of the evaporation
    1804 !-- of rain drops.
     1857   
     1858!------------------------------------------------------------------------------!
     1859! Description:
     1860! ------------
     1861!> This function computes the gamma function (Press et al., 1992).
     1862!> The gamma function is needed for the calculation of the evaporation
     1863!> of rain drops.
     1864!------------------------------------------------------------------------------!
    18051865    FUNCTION gamm( xx )
    18061866       
     
    18121872       IMPLICIT NONE
    18131873
    1814        INTEGER(iwp) ::  j            !:
    1815 
    1816        REAL(wp)     ::  gamm         !:
    1817        REAL(wp)     ::  ser          !:
    1818        REAL(wp)     ::  tmp          !:
    1819        REAL(wp)     ::  x_gamm       !:
    1820        REAL(wp)     ::  xx           !:
    1821        REAL(wp)     ::  y_gamm       !:
     1874       INTEGER(iwp) ::  j            !<
     1875
     1876       REAL(wp)     ::  gamm         !<
     1877       REAL(wp)     ::  ser          !<
     1878       REAL(wp)     ::  tmp          !<
     1879       REAL(wp)     ::  x_gamm       !<
     1880       REAL(wp)     ::  xx           !<
     1881       REAL(wp)     ::  y_gamm       !<
    18221882
    18231883       x_gamm = xx
Note: See TracChangeset for help on using the changeset viewer.