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/nudging.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! 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:
     
    6268    SUBROUTINE init_nudge
    6369
    64        USE arrays_3d
    65        USE control_parameters
    66        USE cpulog
    67        USE indices
    68        USE pegrid
     70       USE arrays_3d,                                                          &
     71           ONLY:  ptnudge, qnudge, timenudge, tnudge, unudge, vnudge, wnudge,  &
     72                  zu
     73
     74       USE control_parameters,                                                 &
     75           ONLY:  dt_3d, lptnudge, lqnudge, lunudge, lvnudge, lwnudge,         &
     76                   message_string, ntnudge
     77
     78       USE indices,                                                            &
     79           ONLY:  nzb, nzt
     80
     81       USE kinds
    6982
    7083       IMPLICIT NONE
    7184
    72        INTEGER :: finput = 90, ierrn, k, t
    73 
    74        CHARACTER(1) :: hash
    75        REAL :: highheight, highqnudge, highptnudge, highunudge, highvnudge, &
    76                highwnudge, hightnudge
    77        REAL :: lowheight, lowqnudge, lowptnudge, lowunudge, lowvnudge, &
    78                lowwnudge, lowtnudge
    79        REAL :: fac
     85
     86       INTEGER(iwp) ::  finput = 90  !:
     87       INTEGER(iwp) ::  ierrn        !:
     88       INTEGER(iwp) ::  k            !:
     89       INTEGER(iwp) ::  t            !:
     90
     91       CHARACTER(1) ::  hash     !:
     92
     93       REAL(wp) ::  highheight   !:
     94       REAL(wp) ::  highqnudge   !:
     95       REAL(wp) ::  highptnudge  !:
     96       REAL(wp) ::  highunudge   !:
     97       REAL(wp) ::  highvnudge   !:
     98       REAL(wp) ::  highwnudge   !:
     99       REAL(wp) ::  hightnudge   !:
     100
     101       REAL(wp) ::  lowheight    !:
     102       REAL(wp) ::  lowqnudge    !:
     103       REAL(wp) ::  lowptnudge   !:
     104       REAL(wp) ::  lowunudge    !:
     105       REAL(wp) ::  lowvnudge    !:
     106       REAL(wp) ::  lowwnudge    !:
     107       REAL(wp) ::  lowtnudge    !:
     108
     109       REAL(wp) ::  fac          !:
    80110
    81111       ALLOCATE( ptnudge(nzb:nzt+1,1:ntnudge), qnudge(nzb:nzt+1,1:ntnudge), &
     
    103133          t = t + 1
    104134          hash = "#"
    105           ierrn = 1 ! not zero       
     135          ierrn = 1 ! not zero
    106136!
    107137!--       Search for the next line consisting of "# time",
     
    160190             fac = ( highheight - zu(k) ) / ( highheight - lowheight )
    161191
    162              tnudge(k,t)  = fac * lowtnudge + ( 1 - fac ) * hightnudge
    163              unudge(k,t)  = fac * lowunudge + ( 1 - fac ) * highunudge
    164              vnudge(k,t)  = fac * lowvnudge + ( 1 - fac ) * highvnudge
    165              wnudge(k,t)  = fac * lowwnudge + ( 1 - fac ) * highwnudge
    166              ptnudge(k,t) = fac * lowptnudge + ( 1 - fac ) * highptnudge
    167              qnudge(k,t)  = fac * lowqnudge + ( 1 - fac ) * highqnudge
     192             tnudge(k,t)  = fac * lowtnudge + ( 1.0 - fac ) * hightnudge
     193             unudge(k,t)  = fac * lowunudge + ( 1.0 - fac ) * highunudge
     194             vnudge(k,t)  = fac * lowvnudge + ( 1.0 - fac ) * highvnudge
     195             wnudge(k,t)  = fac * lowwnudge + ( 1.0 - fac ) * highwnudge
     196             ptnudge(k,t) = fac * lowptnudge + ( 1.0 - fac ) * highptnudge
     197             qnudge(k,t)  = fac * lowqnudge + ( 1.0 - fac ) * highqnudge
    168198          ENDDO
    169199
     
    188218    SUBROUTINE nudge ( time, prog_var )
    189219
    190        USE arrays_3d
    191        USE buoyancy_mod
    192        USE control_parameters
    193        USE cpulog
    194        USE indices
    195        USE pegrid
    196        USE statistics
     220       USE arrays_3d,                                                          &
     221           ONLY:  pt, ptnudge, q, qnudge, tend, timenudge, tnudge, u, unudge,  &
     222                  v, vnudge
     223
     224       USE buoyancy_mod,                                                       &
     225           ONLY:  calc_mean_profile
     226
     227       USE control_parameters,                                                 &
     228           ONLY:  dt_3d, message_string
     229
     230       USE indices,                                                            &
     231           ONLY:  nxl, nxr, nys, nyn, nzb, nzb_u_inner, nzt
     232
     233       USE kinds,                                                              &
     234           ONLY:  iwp, wp
     235
     236       USE statistics,                                                         &
     237           ONLY:  hom
    197238
    198239       IMPLICIT NONE
    199240
    200        CHARACTER (LEN=*) ::  prog_var
    201 
    202        REAL :: currtnudge, dtm, dtp, time
    203 
    204        INTEGER ::  i, j, k, t
     241       CHARACTER (LEN=*) ::  prog_var  !:
     242
     243       REAL(wp) ::  currtnudge  !:
     244       REAL(wp) ::  dtm         !:
     245       REAL(wp) ::  dtp         !:
     246       REAL(wp) ::  time        !:
     247
     248       INTEGER(iwp) ::  i  !:
     249       INTEGER(iwp) ::  j  !:
     250       INTEGER(iwp) ::  k  !:
     251       INTEGER(iwp) ::  t  !:
    205252
    206253
     
    309356    SUBROUTINE nudge_ij( i, j, time, prog_var )
    310357
    311        USE arrays_3d
    312        USE buoyancy_mod
    313        USE control_parameters
    314        USE cpulog
    315        USE indices
    316        USE pegrid
    317        USE statistics
     358       USE arrays_3d,                                                          &
     359           ONLY:  pt, ptnudge, q, qnudge, tend, timenudge, tnudge, u, unudge,  &
     360                  v, vnudge
     361
     362       USE buoyancy_mod,                                                       &
     363           ONLY:  calc_mean_profile
     364
     365       USE control_parameters,                                                 &
     366           ONLY:  dt_3d, message_string
     367
     368       USE indices,                                                            &
     369           ONLY:  nxl, nxr, nys, nyn, nzb, nzb_u_inner, nzt
     370
     371       USE kinds,                                                              &
     372           ONLY:  iwp, wp
     373
     374       USE statistics,                                                         &
     375           ONLY:  hom
    318376
    319377       IMPLICIT NONE
    320378
    321        CHARACTER (LEN=*) ::  prog_var
    322 
    323        REAL :: currtnudge, dtm, dtp, time
    324 
    325        INTEGER ::  i, j, k, t
     379
     380       CHARACTER (LEN=*) ::  prog_var  !:
     381
     382       REAL(wp) ::  currtnudge  !:
     383       REAL(wp) ::  dtm         !:
     384       REAL(wp) ::  dtp         !:
     385       REAL(wp) ::  time        !:
     386
     387       INTEGER(iwp) ::  i  !:
     388       INTEGER(iwp) ::  j  !:
     389       INTEGER(iwp) ::  k  !:
     390       INTEGER(iwp) ::  t  !:
    326391
    327392
Note: See TracChangeset for help on using the changeset viewer.