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

    r1319 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! comment fields (!:) to be used for variable explanations added to
     26! all variable declaration statements
    2327!
    2428! Former revisions:
     
    5963    SUBROUTINE init_ls_forcing
    6064
    61        USE arrays_3d
    62        USE control_parameters
    63        USE cpulog
    64        USE indices
    65        USE pegrid
     65       USE arrays_3d,                                                          &
     66           ONLY:  p_surf, pt_surf, q_surf, qsws_surf, shf_surf, time_surf,     &
     67                  time_vert, ug_vert, vg_vert, wsubs_vert, zu
     68
     69       USE control_parameters,                                                 &
     70           ONLY:  end_time, lsf_surf, lsf_vert, message_string, nlsf
     71
     72       USE indices,                                                            &
     73           ONLY:  nzb, nzt
     74
     75       USE kinds
     76
    6677
    6778       IMPLICIT NONE
    6879
    69        INTEGER ::  finput = 90, ierrn, k, t
    70        CHARACTER (100)::  chmess
    71        CHARACTER(1) ::  hash
    72        REAL ::  r_dummy, fac
    73        REAL ::  highheight, highug_vert, highvg_vert, highwsubs_vert
    74        REAL ::  lowheight, lowug_vert, lowvg_vert, lowwsubs_vert
     80       CHARACTER(100) ::  chmess              !:
     81       CHARACTER(1)   ::  hash                !:
     82
     83       INTEGER(iwp) ::  ierrn                 !:
     84       INTEGER(iwp) ::  finput = 90           !:
     85       INTEGER(iwp) ::  k                     !:
     86       INTEGER(iwp) ::  t                     !:
     87
     88       REAL(wp) ::  fac                       !:
     89       REAL(wp) ::  highheight                !:
     90       REAL(wp) ::  highug_vert               !:
     91       REAL(wp) ::  highvg_vert               !:
     92       REAL(wp) ::  highwsubs_vert            !:
     93       REAL(wp) ::  lowheight                 !:
     94       REAL(wp) ::  lowug_vert                !:
     95       REAL(wp) ::  lowvg_vert                !:
     96       REAL(wp) ::  lowwsubs_vert             !:
     97       REAL(wp) ::  r_dummy                   !:
    7598
    7699       ALLOCATE( p_surf(0:nlsf), pt_surf(0:nlsf), q_surf(0:nlsf),         &
     
    226249    SUBROUTINE ls_forcing_surf ( time )
    227250
    228        USE arrays_3d
    229        USE control_parameters
    230        USE cpulog
    231        USE indices
    232        USE pegrid
     251       USE arrays_3d,                                                          &
     252           ONLY:  p_surf, pt_surf, q_surf, qsws, qsws_surf, shf, shf_surf,     &
     253                  time_surf, time_vert, ug, ug_vert, vg, vg_vert
     254
     255       USE control_parameters,                                                 &
     256           ONLY:  bc_q_b, ibc_pt_b, ibc_q_b, pt_surface, q_surface,            &
     257                  surface_pressure
     258
     259       USE kinds
     260
    233261
    234262       IMPLICIT NONE
    235263
    236        REAL, INTENT(in)  :: time
    237        REAL :: fac
    238        INTEGER :: t
     264       INTEGER(iwp) ::  t                     !:
     265
     266       REAL(wp)             :: fac            !:
     267       REAL(wp), INTENT(in) :: time           !:
    239268
    240269!
     
    284313    SUBROUTINE ls_forcing_vert ( time )
    285314
    286        USE arrays_3d
    287        USE control_parameters
    288        USE cpulog
    289        USE indices
    290        USE pegrid
     315       USE arrays_3d,                                                          &
     316           ONLY:  time_vert, ug, ug_vert, vg, vg_vert, w_subs, wsubs_vert
     317
     318       USE control_parameters,                                                 &
     319           ONLY:  large_scale_subsidence
     320
     321       USE kinds
     322
    291323
    292324       IMPLICIT NONE
    293325
    294        REAL, INTENT(in)  :: time
    295        REAL :: fac
    296        INTEGER :: t
     326       INTEGER(iwp) ::  t                     !:
     327
     328       REAL(wp)             ::  fac           !:
     329       REAL(wp), INTENT(in) ::  time          !:
    297330
    298331!
Note: See TracChangeset for help on using the changeset viewer.