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

    r1399 r1682  
    1  MODULE nudge_mod
    2 
     1!> @file nudging.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    8079! Description:
    8180! ------------
    82 ! Nudges u, v, pt and q to given profiles on a relaxation timescale tnudge.
    83 ! Profiles are read in from NUDGIN_DATA. Code is based on Neggers et al. (2012)
    84 ! and also part of DALES and UCLA-LES.
     81!> Nudges u, v, pt and q to given profiles on a relaxation timescale tnudge.
     82!> Profiles are read in from NUDGIN_DATA. Code is based on Neggers et al. (2012)
     83!> and also part of DALES and UCLA-LES.
    8584!--------------------------------------------------------------------------------!
     85 MODULE nudge_mod
     86 
    8687
    8788    PRIVATE
     
    9697 CONTAINS
    9798
     99!------------------------------------------------------------------------------!
     100! Description:
     101! ------------
     102!> @todo Missing subroutine description.
     103!------------------------------------------------------------------------------!
    98104    SUBROUTINE init_nudge
    99105
     
    114120
    115121
    116        INTEGER(iwp) ::  finput = 90  !:
    117        INTEGER(iwp) ::  ierrn        !:
    118        INTEGER(iwp) ::  k            !:
    119        INTEGER(iwp) ::  nt            !:
    120 
    121        CHARACTER(1) ::  hash     !:
    122 
    123        REAL(wp) ::  highheight   !:
    124        REAL(wp) ::  highqnudge   !:
    125        REAL(wp) ::  highptnudge  !:
    126        REAL(wp) ::  highunudge   !:
    127        REAL(wp) ::  highvnudge   !:
    128        REAL(wp) ::  highwnudge   !:
    129        REAL(wp) ::  hightnudge   !:
    130 
    131        REAL(wp) ::  lowheight    !:
    132        REAL(wp) ::  lowqnudge    !:
    133        REAL(wp) ::  lowptnudge   !:
    134        REAL(wp) ::  lowunudge    !:
    135        REAL(wp) ::  lowvnudge    !:
    136        REAL(wp) ::  lowwnudge    !:
    137        REAL(wp) ::  lowtnudge    !:
    138 
    139        REAL(wp) ::  fac          !:
     122       INTEGER(iwp) ::  finput = 90  !<
     123       INTEGER(iwp) ::  ierrn        !<
     124       INTEGER(iwp) ::  k            !<
     125       INTEGER(iwp) ::  nt            !<
     126
     127       CHARACTER(1) ::  hash     !<
     128
     129       REAL(wp) ::  highheight   !<
     130       REAL(wp) ::  highqnudge   !<
     131       REAL(wp) ::  highptnudge  !<
     132       REAL(wp) ::  highunudge   !<
     133       REAL(wp) ::  highvnudge   !<
     134       REAL(wp) ::  highwnudge   !<
     135       REAL(wp) ::  hightnudge   !<
     136
     137       REAL(wp) ::  lowheight    !<
     138       REAL(wp) ::  lowqnudge    !<
     139       REAL(wp) ::  lowptnudge   !<
     140       REAL(wp) ::  lowunudge    !<
     141       REAL(wp) ::  lowvnudge    !<
     142       REAL(wp) ::  lowwnudge    !<
     143       REAL(wp) ::  lowtnudge    !<
     144
     145       REAL(wp) ::  fac          !<
    140146
    141147       ALLOCATE( ptnudge(nzb:nzt+1,1:ntnudge), qnudge(nzb:nzt+1,1:ntnudge), &
     
    251257
    252258
     259!------------------------------------------------------------------------------!
     260! Description:
     261! ------------
     262!> @todo Missing subroutine description.
     263!------------------------------------------------------------------------------!
    253264    SUBROUTINE calc_tnudge ( time )
    254265
     
    267278
    268279
    269        REAL(wp) ::  dtm         !:
    270        REAL(wp) ::  dtp         !:
    271        REAL(wp) ::  time        !:
    272 
    273        INTEGER(iwp) ::  k   !:
    274        INTEGER(iwp) ::  nt  !:
     280       REAL(wp) ::  dtm         !<
     281       REAL(wp) ::  dtp         !<
     282       REAL(wp) ::  time        !<
     283
     284       INTEGER(iwp) ::  k   !<
     285       INTEGER(iwp) ::  nt  !<
    275286
    276287       nt = 1
     
    292303
    293304!------------------------------------------------------------------------------!
    294 ! Call for all grid points
     305! Description:
     306! ------------
     307!> Call for all grid points
    295308!------------------------------------------------------------------------------!
    296309    SUBROUTINE nudge ( time, prog_var )
     
    313326       IMPLICIT NONE
    314327
    315        CHARACTER (LEN=*) ::  prog_var  !:
    316 
    317        REAL(wp) ::  tmp_tend    !:
    318        REAL(wp) ::  dtm         !:
    319        REAL(wp) ::  dtp         !:
    320        REAL(wp) ::  time        !:
    321 
    322        INTEGER(iwp) ::  i  !:
    323        INTEGER(iwp) ::  j  !:
    324        INTEGER(iwp) ::  k  !:
    325        INTEGER(iwp) ::  nt  !:
     328       CHARACTER (LEN=*) ::  prog_var  !<
     329
     330       REAL(wp) ::  tmp_tend    !<
     331       REAL(wp) ::  dtm         !<
     332       REAL(wp) ::  dtp         !<
     333       REAL(wp) ::  time        !<
     334
     335       INTEGER(iwp) ::  i  !<
     336       INTEGER(iwp) ::  j  !<
     337       INTEGER(iwp) ::  k  !<
     338       INTEGER(iwp) ::  nt  !<
    326339
    327340
     
    433446
    434447!------------------------------------------------------------------------------!
    435 ! Call for grid point i,j
     448! Description:
     449! ------------
     450!> Call for grid point i,j
    436451!------------------------------------------------------------------------------!
    437452
     
    456471
    457472
    458        CHARACTER (LEN=*) ::  prog_var  !:
    459 
    460        REAL(wp) ::  tmp_tend    !:
    461        REAL(wp) ::  dtm         !:
    462        REAL(wp) ::  dtp         !:
    463        REAL(wp) ::  time        !:
    464 
    465        INTEGER(iwp) ::  i  !:
    466        INTEGER(iwp) ::  j  !:
    467        INTEGER(iwp) ::  k  !:
    468        INTEGER(iwp) ::  nt  !:
     473       CHARACTER (LEN=*) ::  prog_var  !<
     474
     475       REAL(wp) ::  tmp_tend    !<
     476       REAL(wp) ::  dtm         !<
     477       REAL(wp) ::  dtp         !<
     478       REAL(wp) ::  time        !<
     479
     480       INTEGER(iwp) ::  i  !<
     481       INTEGER(iwp) ::  j  !<
     482       INTEGER(iwp) ::  k  !<
     483       INTEGER(iwp) ::  nt  !<
    469484
    470485
     
    553568
    554569
     570!------------------------------------------------------------------------------!
     571! Description:
     572! ------------
     573!> @todo Missing subroutine description.
     574!------------------------------------------------------------------------------!
    555575    SUBROUTINE nudge_ref ( time )
    556576
     
    564584       IMPLICIT NONE
    565585
    566        INTEGER(iwp) ::  nt                    !:
    567 
    568        REAL(wp)             ::  fac           !:
    569        REAL(wp), INTENT(in) ::  time          !:
     586       INTEGER(iwp) ::  nt                    !<
     587
     588       REAL(wp)             ::  fac           !<
     589       REAL(wp), INTENT(in) ::  time          !<
    570590
    571591!
Note: See TracChangeset for help on using the changeset viewer.