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

    r1354 r1682  
    1  MODULE calc_radiation_mod
    2 
     1!> @file calc_radiation.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4948! Description:
    5049! -------------
    51 ! Calculation of the vertical divergences of the long-wave radiation-fluxes
    52 ! based on the parameterization of the cloud effective emissivity
    53 !------------------------------------------------------------------------------!
     50!> Calculation of the vertical divergences of the long-wave radiation-fluxes
     51!> based on the parameterization of the cloud effective emissivity
     52!------------------------------------------------------------------------------!
     53 MODULE calc_radiation_mod
     54 
    5455    USE kinds
    5556   
     
    5758    PUBLIC calc_radiation
    5859   
    59     LOGICAL, SAVE ::  first_call = .TRUE. !:
    60     REAL(wp), SAVE ::  sigma = 5.67E-08_wp   !:
    61 
    62     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  lwp_ground         !:
    63     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  lwp_top            !:
    64     REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  blackbody_emission !:
     60    LOGICAL, SAVE ::  first_call = .TRUE. !<
     61    REAL(wp), SAVE ::  sigma = 5.67E-08_wp   !<
     62
     63    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  lwp_ground         !<
     64    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  lwp_top            !<
     65    REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE ::  blackbody_emission !<
    6566
    6667    INTERFACE calc_radiation
     
    7374
    7475!------------------------------------------------------------------------------!
    75 ! Call for all grid points
     76! Description:
     77! ------------
     78!> Call for all grid points
    7679!------------------------------------------------------------------------------!
    7780    SUBROUTINE calc_radiation
     
    9699       IMPLICIT NONE
    97100
    98        INTEGER(iwp) ::  i      !:
    99        INTEGER(iwp) ::  j      !:
    100        INTEGER(iwp) ::  k      !:
    101        INTEGER(iwp) ::  k_help !:
     101       INTEGER(iwp) ::  i      !<
     102       INTEGER(iwp) ::  j      !<
     103       INTEGER(iwp) ::  k      !<
     104       INTEGER(iwp) ::  k_help !<
    102105 
    103        REAL(wp) :: df_p                      !:
    104        REAL(wp) :: df_m                      !:
    105        REAL(wp) :: effective_emission_up_m   !:
    106        REAL(wp) :: effective_emission_up_p   !:
    107        REAL(wp) :: effective_emission_down_m !:
    108        REAL(wp) :: effective_emission_down_p !:
    109        REAL(wp) :: f_up_m                    !:
    110        REAL(wp) :: f_up_p                    !:
    111        REAL(wp) :: f_down_m                  !:
    112        REAL(wp) :: f_down_p                  !:
    113        REAL(wp) :: impinging_flux_at_top     !:
    114        REAL(wp) :: temperature               !:
     106       REAL(wp) :: df_p                      !<
     107       REAL(wp) :: df_m                      !<
     108       REAL(wp) :: effective_emission_up_m   !<
     109       REAL(wp) :: effective_emission_up_p   !<
     110       REAL(wp) :: effective_emission_down_m !<
     111       REAL(wp) :: effective_emission_down_p !<
     112       REAL(wp) :: f_up_m                    !<
     113       REAL(wp) :: f_up_p                    !<
     114       REAL(wp) :: f_down_m                  !<
     115       REAL(wp) :: f_down_p                  !<
     116       REAL(wp) :: impinging_flux_at_top     !<
     117       REAL(wp) :: temperature               !<
    115118
    116119
     
    216219
    217220!------------------------------------------------------------------------------!
    218 ! Call for grid point i,j
     221! Description:
     222! ------------
     223!> Call for grid point i,j
    219224!------------------------------------------------------------------------------!
    220225    SUBROUTINE calc_radiation_ij( i, j )
     
    239244       IMPLICIT NONE
    240245
    241        INTEGER(iwp) ::  i      !:
    242        INTEGER(iwp) ::  j      !:
    243        INTEGER(iwp) ::  k      !:
    244        INTEGER(iwp) ::  k_help !:
    245 
    246        REAL(wp) :: df_p                      !:
    247        REAL(wp) :: df_m                      !:
    248        REAL(wp) :: effective_emission_up_m   !:
    249        REAL(wp) :: effective_emission_up_p   !:
    250        REAL(wp) :: effective_emission_down_m !:
    251        REAL(wp) :: effective_emission_down_p !:
    252        REAL(wp) :: f_up_m                    !:
    253        REAL(wp) :: f_up_p                    !:
    254        REAL(wp) :: f_down_m                  !:
    255        REAL(wp) :: f_down_p                  !:
    256        REAL(wp) :: impinging_flux_at_top     !:
    257        REAL(wp) :: temperature               !:
     246       INTEGER(iwp) ::  i      !<
     247       INTEGER(iwp) ::  j      !<
     248       INTEGER(iwp) ::  k      !<
     249       INTEGER(iwp) ::  k_help !<
     250
     251       REAL(wp) :: df_p                      !<
     252       REAL(wp) :: df_m                      !<
     253       REAL(wp) :: effective_emission_up_m   !<
     254       REAL(wp) :: effective_emission_up_p   !<
     255       REAL(wp) :: effective_emission_down_m !<
     256       REAL(wp) :: effective_emission_down_p !<
     257       REAL(wp) :: f_up_m                    !<
     258       REAL(wp) :: f_up_p                    !<
     259       REAL(wp) :: f_down_m                  !<
     260       REAL(wp) :: f_down_p                  !<
     261       REAL(wp) :: impinging_flux_at_top     !<
     262       REAL(wp) :: temperature               !<
    258263
    259264       
Note: See TracChangeset for help on using the changeset viewer.