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

    r1354 r1682  
    1  SUBROUTINE init_1d_model
    2 
     1!> @file init_1d_model.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6665! Description:
    6766! ------------
    68 ! 1D-model to initialize the 3D-arrays.
    69 ! The temperature profile is set as steady and a corresponding steady solution
    70 ! of the wind profile is being computed.
    71 ! All subroutines required can be found within this file.
     67!> 1D-model to initialize the 3D-arrays.
     68!> The temperature profile is set as steady and a corresponding steady solution
     69!> of the wind profile is being computed.
     70!> All subroutines required can be found within this file.
    7271!------------------------------------------------------------------------------!
     72 SUBROUTINE init_1d_model
     73 
    7374
    7475    USE arrays_3d,                                                             &
     
    9394    IMPLICIT NONE
    9495
    95     CHARACTER (LEN=9) ::  time_to_string  !:
    96    
    97     INTEGER(iwp) ::  k  !:
    98    
    99     REAL(wp) ::  lambda !:
     96    CHARACTER (LEN=9) ::  time_to_string  !<
     97   
     98    INTEGER(iwp) ::  k  !<
     99   
     100    REAL(wp) ::  lambda !<
    100101
    101102!
     
    196197
    197198
    198  SUBROUTINE time_integration_1d
    199 
    200199!------------------------------------------------------------------------------!
    201200! Description:
    202201! ------------
    203 ! Leap-frog time differencing scheme for the 1D-model.
     202!> Leap-frog time differencing scheme for the 1D-model.
    204203!------------------------------------------------------------------------------!
     204 
     205 SUBROUTINE time_integration_1d
     206
    205207
    206208    USE arrays_3d,                                                             &
     
    231233    IMPLICIT NONE
    232234
    233     CHARACTER (LEN=9) ::  time_to_string  !:
    234    
    235     INTEGER(iwp) ::  k  !:
    236    
    237     REAL(wp) ::  a            !:
    238     REAL(wp) ::  b            !:
    239     REAL(wp) ::  dissipation  !:
    240     REAL(wp) ::  dpt_dz       !:
    241     REAL(wp) ::  flux         !:
    242     REAL(wp) ::  kmzm         !:
    243     REAL(wp) ::  kmzp         !:
    244     REAL(wp) ::  l_stable     !:
    245     REAL(wp) ::  pt_0         !:
    246     REAL(wp) ::  uv_total     !:
     235    CHARACTER (LEN=9) ::  time_to_string  !<
     236   
     237    INTEGER(iwp) ::  k  !<
     238   
     239    REAL(wp) ::  a            !<
     240    REAL(wp) ::  b            !<
     241    REAL(wp) ::  dissipation  !<
     242    REAL(wp) ::  dpt_dz       !<
     243    REAL(wp) ::  flux         !<
     244    REAL(wp) ::  kmzm         !<
     245    REAL(wp) ::  kmzp         !<
     246    REAL(wp) ::  l_stable     !<
     247    REAL(wp) ::  pt_0         !<
     248    REAL(wp) ::  uv_total     !<
    247249
    248250!
     
    741743
    742744
    743  SUBROUTINE run_control_1d
    744 
    745745!------------------------------------------------------------------------------!
    746746! Description:
    747747! ------------
    748 ! Compute and print out quantities for run control of the 1D model.
     748!> Compute and print out quantities for run control of the 1D model.
    749749!------------------------------------------------------------------------------!
     750 
     751 SUBROUTINE run_control_1d
     752
    750753
    751754    USE constants,                                                             &
     
    768771    IMPLICIT NONE
    769772
    770     INTEGER(iwp) ::  k  !:
     773    INTEGER(iwp) ::  k  !<
    771774   
    772775    REAL(wp) ::  alpha
     
    828831
    829832
    830  SUBROUTINE timestep_1d
    831 
    832833!------------------------------------------------------------------------------!
    833834! Description:
    834835! ------------
    835 ! Compute the time step w.r.t. the diffusion criterion
     836!> Compute the time step w.r.t. the diffusion criterion
    836837!------------------------------------------------------------------------------!
     838 
     839 SUBROUTINE timestep_1d
     840
    837841
    838842    USE arrays_3d,                                                             &
     
    854858    IMPLICIT NONE
    855859
    856     INTEGER(iwp) ::  k !:
    857    
    858     REAL(wp) ::  div      !:
    859     REAL(wp) ::  dt_diff  !:
    860     REAL(wp) ::  fac      !:
    861     REAL(wp) ::  value    !:
     860    INTEGER(iwp) ::  k !<
     861   
     862    REAL(wp) ::  div      !<
     863    REAL(wp) ::  dt_diff  !<
     864    REAL(wp) ::  fac      !<
     865    REAL(wp) ::  value    !<
    862866
    863867
     
    901905
    902906
    903  SUBROUTINE print_1d_model
    904 
    905907!------------------------------------------------------------------------------!
    906908! Description:
    907909! ------------
    908 ! List output of profiles from the 1D-model
     910!> List output of profiles from the 1D-model
    909911!------------------------------------------------------------------------------!
     912 
     913 SUBROUTINE print_1d_model
     914
    910915
    911916    USE arrays_3d,                                                             &
     
    928933
    929934
    930     INTEGER(iwp) ::  k  !:
     935    INTEGER(iwp) ::  k  !<
    931936
    932937
Note: See TracChangeset for help on using the changeset viewer.