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_1d_model.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:
     
    4147! 978 2012-08-09 08:28:32Z fricke
    4248! roughness length for scalar quantities z0h1d added
    43 !
    44 ! 667 2010-12-23 12:06:00Z suehring/gryschka
    45 ! replaced mirror boundary conditions for u and v  at the ground
    46 ! by dirichlet boundary conditions
    47 !
    48 ! 254 2009-03-05 15:33:42Z heinze
    49 ! Output of messages replaced by message handling routine.
    50 !
    51 ! 184 2008-08-04 15:53:39Z letzel
    52 ! provisional solution for run_control_1d output: add 'CALL check_open( 15 )'
    53 !
    54 ! 135 2007-11-22 12:24:23Z raasch
    55 ! Bugfix: absolute value of f must be used when calculating the Blackadar
    56 ! mixing length
    57 !
    58 ! 82 2007-04-16 15:40:52Z raasch
    59 ! Preprocessor strings for different linux clusters changed to "lc",
    60 ! routine local_flush is used for buffer flushing
    61 !
    62 ! 75 2007-03-22 09:54:05Z raasch
    63 ! Bugfix: preset of tendencies te_em, te_um, te_vm,
    64 ! moisture renamed humidity
    65 !
    66 ! RCS Log replace by Id keyword, revision history cleaned up
    67 !
    68 ! Revision 1.21  2006/06/02 15:19:57  raasch
    69 ! cpp-directives extended for lctit
    7049!
    7150! Revision 1.1  1998/03/09 16:22:10  raasch
     
    8160!------------------------------------------------------------------------------!
    8261
    83     USE arrays_3d
    84     USE indices
    85     USE model_1d
    86     USE control_parameters
     62    USE arrays_3d,                                                             &
     63        ONLY:  l_grid, ug, u_init, vg, v_init, zu
     64   
     65    USE indices,                                                               &
     66        ONLY:  nzb, nzt
     67   
     68    USE kinds
     69   
     70    USE model_1d,                                                              &
     71        ONLY:  e1d, e1d_p, kh1d, km1d, l1d, l_black, qs1d, rif1d,              &
     72               simulated_time_1d, te_e, te_em, te_u, te_um, te_v, te_vm, ts1d, &
     73               u1d, u1d_p, us1d, usws1d, v1d, v1d_p, vsws1d, z01d, z0h1d
     74   
     75    USE control_parameters,                                                    &
     76        ONLY:  constant_diffusion, f, humidity, kappa, km_constant,            &
     77               mixing_length_1d, passive_scalar, prandtl_layer,                &
     78               prandtl_number, roughness_length, simulated_time_chr,           &
     79               z0h_factor
    8780
    8881    IMPLICIT NONE
    8982
    90     CHARACTER (LEN=9) ::  time_to_string
    91     INTEGER ::  k
    92     REAL    ::  lambda
     83    CHARACTER (LEN=9) ::  time_to_string  !:
     84   
     85    INTEGER(iwp) ::  k  !:
     86   
     87    REAL(wp) ::  lambda !:
    9388
    9489!
    9590!-- Allocate required 1D-arrays
    96     ALLOCATE( e1d(nzb:nzt+1),    e1d_p(nzb:nzt+1), &
    97               kh1d(nzb:nzt+1),   km1d(nzb:nzt+1),  &
    98               l_black(nzb:nzt+1), l1d(nzb:nzt+1),   &
    99               rif1d(nzb:nzt+1),   te_e(nzb:nzt+1),  &
    100               te_em(nzb:nzt+1),  te_u(nzb:nzt+1),    te_um(nzb:nzt+1), &
    101               te_v(nzb:nzt+1),   te_vm(nzb:nzt+1),    u1d(nzb:nzt+1),   &
    102               u1d_p(nzb:nzt+1),  v1d(nzb:nzt+1),   &
     91    ALLOCATE( e1d(nzb:nzt+1),    e1d_p(nzb:nzt+1),                             &
     92              kh1d(nzb:nzt+1),   km1d(nzb:nzt+1),                              &
     93              l_black(nzb:nzt+1), l1d(nzb:nzt+1),                              &
     94              rif1d(nzb:nzt+1),   te_e(nzb:nzt+1),                             &
     95              te_em(nzb:nzt+1),  te_u(nzb:nzt+1),    te_um(nzb:nzt+1),         &
     96              te_v(nzb:nzt+1),   te_vm(nzb:nzt+1),    u1d(nzb:nzt+1),          &
     97              u1d_p(nzb:nzt+1),  v1d(nzb:nzt+1),                               &
    10398              v1d_p(nzb:nzt+1) )
    10499
     
    120115!--       Blackadar mixing length
    121116          IF ( f /= 0.0 )  THEN
    122              lambda = 2.7E-4 * SQRT( ug(nzt+1)**2 + vg(nzt+1)**2 ) / &
     117             lambda = 2.7E-4 * SQRT( ug(nzt+1)**2 + vg(nzt+1)**2 ) /           &
    123118                               ABS( f ) + 1E-10
    124119          ELSE
     
    197192!------------------------------------------------------------------------------!
    198193
    199     USE arrays_3d
    200     USE control_parameters
    201     USE indices
    202     USE model_1d
     194    USE arrays_3d,                                                             &
     195        ONLY:  dd2zu, ddzu, ddzw, l_grid, pt_init, q_init, ug, vg, zu
     196       
     197    USE control_parameters,                                                    &
     198        ONLY:  constant_diffusion, dissipation_1d, humidity,                   &
     199               intermediate_timestep_count, intermediate_timestep_count_max,   &
     200               f, g, ibc_e_b, kappa, mixing_length_1d, passive_scalar,         &
     201               prandtl_layer, rif_max, rif_min, simulated_time_chr,            &
     202               timestep_scheme, tsc
     203               
     204    USE indices,                                                               &
     205        ONLY:  nzb, nzb_diff, nzt
     206       
     207    USE kinds
     208   
     209    USE model_1d,                                                              &
     210        ONLY:  current_timestep_number_1d, damp_level_ind_1d, dt_1d,           &
     211               dt_pr_1d, dt_run_control_1d, e1d, e1d_p, end_time_1d,           &
     212               kh1d, km1d, l1d, l_black, qs1d, rif1d, simulated_time_1d,       &
     213               stop_dt_1d, te_e, te_em, te_u, te_um, te_v, te_vm, time_pr_1d,  &
     214               ts1d, time_run_control_1d, u1d, u1d_p, us1d, usws1d, v1d,       &
     215               v1d_p, vsws1d, z01d, z0h1d
     216       
    203217    USE pegrid
    204218
    205219    IMPLICIT NONE
    206220
    207     CHARACTER (LEN=9) ::  time_to_string
    208     INTEGER ::  k
    209     REAL    ::  a, b, dissipation, dpt_dz, flux, kmzm, kmzp, l_stable, pt_0, &
    210                 uv_total
     221    CHARACTER (LEN=9) ::  time_to_string  !:
     222   
     223    INTEGER(iwp) ::  k  !:
     224   
     225    REAL(wp) ::  a            !:
     226    REAL(wp) ::  b            !:
     227    REAL(wp) ::  dissipation  !:
     228    REAL(wp) ::  dpt_dz       !:
     229    REAL(wp) ::  flux         !:
     230    REAL(wp) ::  kmzm         !:
     231    REAL(wp) ::  kmzp         !:
     232    REAL(wp) ::  l_stable     !:
     233    REAL(wp) ::  pt_0         !:
     234    REAL(wp) ::  uv_total     !:
    211235
    212236!
     
    704728!------------------------------------------------------------------------------!
    705729
    706     USE constants
    707     USE indices
    708     USE model_1d
     730    USE constants,                                                             &
     731        ONLY:  pi
     732       
     733    USE indices,                                                               &
     734        ONLY:  nzb, nzt
     735       
     736    USE kinds
     737   
     738    USE model_1d,                                                              &
     739        ONLY:  current_timestep_number_1d, dt_1d, run_control_header_1d, u1d,  &
     740               us1d, v1d
     741   
    709742    USE pegrid
    710     USE control_parameters
     743   
     744    USE control_parameters,                                                    &
     745        ONLY:  simulated_time_chr
    711746
    712747    IMPLICIT NONE
    713748
    714     INTEGER ::  k
    715     REAL    ::  alpha, energy, umax, uv_total, vmax
     749    INTEGER(iwp) ::  k  !:
     750   
     751    REAL(wp) ::  alpha
     752    REAL(wp) ::  energy
     753    REAL(wp) ::  umax
     754    REAL(wp) ::  uv_total
     755    REAL(wp) ::  vmax
    716756
    717757!
     
    775815!------------------------------------------------------------------------------!
    776816
    777     USE arrays_3d
    778     USE indices
    779     USE model_1d
     817    USE arrays_3d,                                                             &
     818        ONLY:  dzu, zu
     819       
     820    USE indices,                                                               &
     821        ONLY:  nzb, nzt
     822   
     823    USE kinds
     824   
     825    USE model_1d,                                                              &
     826        ONLY:  dt_1d, dt_max_1d, km1d, old_dt_1d, stop_dt_1d
     827   
    780828    USE pegrid
    781     USE control_parameters
     829   
     830    USE control_parameters,                                                              &
     831        ONLY:  message_string
    782832
    783833    IMPLICIT NONE
    784834
    785     INTEGER ::  k
    786     REAL    ::  div, dt_diff, fac, value
     835    INTEGER(iwp) ::  k !:
     836   
     837    REAL(wp) ::  div      !:
     838    REAL(wp) ::  dt_diff  !:
     839    REAL(wp) ::  fac      !:
     840    REAL(wp) ::  value    !:
    787841
    788842
     
    834888!------------------------------------------------------------------------------!
    835889
    836     USE arrays_3d
    837     USE indices
    838     USE model_1d
     890    USE arrays_3d,                                                             &
     891        ONLY:  pt_init, zu
     892       
     893    USE indices,                                                               &
     894        ONLY:  nzb, nzt
     895       
     896    USE kinds
     897   
     898    USE model_1d,                                                              &
     899        ONLY:  e1d, kh1d, km1d, l1d, rif1d, u1d, v1d
     900   
    839901    USE pegrid
    840     USE control_parameters
     902   
     903    USE control_parameters,                                                    &
     904        ONLY:  run_description_header, simulated_time_chr
    841905
    842906    IMPLICIT NONE
    843907
    844908
    845     INTEGER ::  k
     909    INTEGER(iwp) ::  k  !:
    846910
    847911
Note: See TracChangeset for help on using the changeset viewer.