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

    r1603 r1682  
    1  MODULE ls_forcing_mod
    2 
     1!> @file ls_forcing.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    7170! Description:
    7271! ------------
    73 ! Calculates large scale forcings (geostrophic wind and subsidence velocity) as
    74 ! well as surfaces fluxes dependent on time given in an external file (LSF_DATA).
    75 ! Code is based in parts on DALES and UCLA-LES.
     72!> Calculates large scale forcings (geostrophic wind and subsidence velocity) as
     73!> well as surfaces fluxes dependent on time given in an external file (LSF_DATA).
     74!> Code is based in parts on DALES and UCLA-LES.
    7675!--------------------------------------------------------------------------------!
     76 MODULE ls_forcing_mod
     77 
    7778
    7879    PRIVATE
     
    8788 CONTAINS
    8889
     90!------------------------------------------------------------------------------!
     91! Description:
     92! ------------
     93!> @todo Missing subroutine description.
     94!------------------------------------------------------------------------------!
    8995    SUBROUTINE init_ls_forcing
    9096
     
    108114       IMPLICIT NONE
    109115
    110        CHARACTER(100) ::  chmess      !:
    111        CHARACTER(1)   ::  hash        !:
    112 
    113        INTEGER(iwp) ::  ierrn         !:
    114        INTEGER(iwp) ::  finput = 90   !:
    115        INTEGER(iwp) ::  k             !:
    116        INTEGER(iwp) ::  nt             !:
    117 
    118        REAL(wp) ::  fac               !:
    119        REAL(wp) ::  highheight        !:
    120        REAL(wp) ::  highug_vert       !:
    121        REAL(wp) ::  highvg_vert       !:
    122        REAL(wp) ::  highwsubs_vert    !:
    123        REAL(wp) ::  lowheight         !:
    124        REAL(wp) ::  lowug_vert        !:
    125        REAL(wp) ::  lowvg_vert        !:
    126        REAL(wp) ::  lowwsubs_vert     !:
    127        REAL(wp) ::  high_td_lsa_lpt   !:
    128        REAL(wp) ::  low_td_lsa_lpt    !:
    129        REAL(wp) ::  high_td_lsa_q     !:
    130        REAL(wp) ::  low_td_lsa_q      !:
    131        REAL(wp) ::  high_td_sub_lpt   !:
    132        REAL(wp) ::  low_td_sub_lpt    !:
    133        REAL(wp) ::  high_td_sub_q     !:
    134        REAL(wp) ::  low_td_sub_q      !:
    135        REAL(wp) ::  r_dummy           !:
     116       CHARACTER(100) ::  chmess      !<
     117       CHARACTER(1)   ::  hash        !<
     118
     119       INTEGER(iwp) ::  ierrn         !<
     120       INTEGER(iwp) ::  finput = 90   !<
     121       INTEGER(iwp) ::  k             !<
     122       INTEGER(iwp) ::  nt             !<
     123
     124       REAL(wp) ::  fac               !<
     125       REAL(wp) ::  highheight        !<
     126       REAL(wp) ::  highug_vert       !<
     127       REAL(wp) ::  highvg_vert       !<
     128       REAL(wp) ::  highwsubs_vert    !<
     129       REAL(wp) ::  lowheight         !<
     130       REAL(wp) ::  lowug_vert        !<
     131       REAL(wp) ::  lowvg_vert        !<
     132       REAL(wp) ::  lowwsubs_vert     !<
     133       REAL(wp) ::  high_td_lsa_lpt   !<
     134       REAL(wp) ::  low_td_lsa_lpt    !<
     135       REAL(wp) ::  high_td_lsa_q     !<
     136       REAL(wp) ::  low_td_lsa_q      !<
     137       REAL(wp) ::  high_td_sub_lpt   !<
     138       REAL(wp) ::  low_td_sub_lpt    !<
     139       REAL(wp) ::  high_td_sub_q     !<
     140       REAL(wp) ::  low_td_sub_q      !<
     141       REAL(wp) ::  r_dummy           !<
    136142
    137143       ALLOCATE( p_surf(0:nlsf), pt_surf(0:nlsf), q_surf(0:nlsf),              &
     
    323329
    324330
     331!------------------------------------------------------------------------------!
     332! Description:
     333! ------------
     334!> @todo Missing subroutine description.
     335!------------------------------------------------------------------------------!
    325336    SUBROUTINE ls_forcing_surf ( time )
    326337
     
    337348       IMPLICIT NONE
    338349
    339        INTEGER(iwp) ::  nt                     !:
    340 
    341        REAL(wp)             :: fac            !:
    342        REAL(wp), INTENT(in) :: time           !:
     350       INTEGER(iwp) ::  nt                     !<
     351
     352       REAL(wp)             :: fac            !<
     353       REAL(wp), INTENT(in) :: time           !<
    343354
    344355!
     
    386397
    387398
     399!------------------------------------------------------------------------------!
     400! Description:
     401! ------------
     402!> @todo Missing subroutine description.
     403!------------------------------------------------------------------------------!
    388404    SUBROUTINE ls_forcing_vert ( time )
    389405
     
    398414       IMPLICIT NONE
    399415
    400        INTEGER(iwp) ::  nt                     !:
    401 
    402        REAL(wp)             ::  fac           !:
    403        REAL(wp), INTENT(in) ::  time          !:
     416       INTEGER(iwp) ::  nt                     !<
     417
     418       REAL(wp)             ::  fac           !<
     419       REAL(wp), INTENT(in) ::  time          !<
    404420
    405421!
     
    427443
    428444!------------------------------------------------------------------------------!
    429 ! Call for all grid points
     445! Description:
     446! ------------
     447!> Call for all grid points
    430448!------------------------------------------------------------------------------!
    431449    SUBROUTINE ls_advec ( time, prog_var )
     
    443461       IMPLICIT NONE
    444462
    445        CHARACTER (LEN=*) ::  prog_var   !:
    446 
    447        REAL(wp), INTENT(in)  :: time    !:
    448        REAL(wp) :: fac                  !: 
    449 
    450        INTEGER(iwp) ::  i               !:
    451        INTEGER(iwp) ::  j               !:
    452        INTEGER(iwp) ::  k               !:
    453        INTEGER(iwp) ::  nt               !:
     463       CHARACTER (LEN=*) ::  prog_var   !<
     464
     465       REAL(wp), INTENT(in)  :: time    !<
     466       REAL(wp) :: fac                  !< 
     467
     468       INTEGER(iwp) ::  i               !<
     469       INTEGER(iwp) ::  j               !<
     470       INTEGER(iwp) ::  k               !<
     471       INTEGER(iwp) ::  nt               !<
    454472
    455473!
     
    529547
    530548!------------------------------------------------------------------------------!
    531 ! Call for grid point i,j
     549! Description:
     550! ------------
     551!> Call for grid point i,j
    532552!------------------------------------------------------------------------------!
    533553    SUBROUTINE ls_advec_ij ( i, j, time, prog_var )
     
    545565       IMPLICIT NONE
    546566
    547        CHARACTER (LEN=*) ::  prog_var   !:
    548 
    549        REAL(wp), INTENT(in)  :: time    !:
    550        REAL(wp) :: fac                  !:
    551 
    552        INTEGER(iwp) ::  i               !:
    553        INTEGER(iwp) ::  j               !:
    554        INTEGER(iwp) ::  k               !:
    555        INTEGER(iwp) ::  nt               !:
     567       CHARACTER (LEN=*) ::  prog_var   !<
     568
     569       REAL(wp), INTENT(in)  :: time    !<
     570       REAL(wp) :: fac                  !<
     571
     572       INTEGER(iwp) ::  i               !<
     573       INTEGER(iwp) ::  j               !<
     574       INTEGER(iwp) ::  k               !<
     575       INTEGER(iwp) ::  nt               !<
    556576
    557577!
Note: See TracChangeset for help on using the changeset viewer.