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

    r1586 r1682  
    1  MODULE prognostic_equations_mod
    2 
     1!> @file prognostic_equations.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    161160! Description:
    162161! ------------
    163 ! Solving the prognostic equations.
     162!> Solving the prognostic equations.
    164163!------------------------------------------------------------------------------!
     164 MODULE prognostic_equations_mod
     165
     166 
    165167
    166168    USE arrays_3d,                                                             &
     
    313315
    314316
     317!------------------------------------------------------------------------------!
     318! Description:
     319! ------------
     320!> Version with one optimized loop over all equations. It is only allowed to
     321!> be called for the Wicker and Skamarock or Piascek-Williams advection scheme.
     322!>
     323!> Here the calls of most subroutines are embedded in two DO loops over i and j,
     324!> so communication between CPUs is not allowed (does not make sense) within
     325!> these loops.
     326!>
     327!> (Optimized to avoid cache missings, i.e. for Power4/5-architectures.)
     328!------------------------------------------------------------------------------!
     329 
    315330 SUBROUTINE prognostic_equations_cache
    316331
    317 !------------------------------------------------------------------------------!
    318 ! Version with one optimized loop over all equations. It is only allowed to
    319 ! be called for the Wicker and Skamarock or Piascek-Williams advection scheme.
    320 !
    321 ! Here the calls of most subroutines are embedded in two DO loops over i and j,
    322 ! so communication between CPUs is not allowed (does not make sense) within
    323 ! these loops.
    324 !
    325 ! (Optimized to avoid cache missings, i.e. for Power4/5-architectures.)
    326 !------------------------------------------------------------------------------!
    327332
    328333    IMPLICIT NONE
    329334
    330     INTEGER(iwp) ::  i                   !:
    331     INTEGER(iwp) ::  i_omp_start         !:
    332     INTEGER(iwp) ::  j                   !:
    333     INTEGER(iwp) ::  k                   !:
    334     INTEGER(iwp) ::  omp_get_thread_num  !:
    335     INTEGER(iwp) ::  tn = 0              !:
     335    INTEGER(iwp) ::  i                   !<
     336    INTEGER(iwp) ::  i_omp_start         !<
     337    INTEGER(iwp) ::  j                   !<
     338    INTEGER(iwp) ::  k                   !<
     339    INTEGER(iwp) ::  omp_get_thread_num  !<
     340    INTEGER(iwp) ::  tn = 0              !<
    336341   
    337     LOGICAL      ::  loop_start          !:
     342    LOGICAL      ::  loop_start          !<
    338343
    339344
     
    934939
    935940
     941!------------------------------------------------------------------------------!
     942! Description:
     943! ------------
     944!> Version for vector machines
     945!------------------------------------------------------------------------------!
     946 
    936947 SUBROUTINE prognostic_equations_vector
    937948
    938 !------------------------------------------------------------------------------!
    939 ! Version for vector machines
    940 !------------------------------------------------------------------------------!
    941949
    942950    IMPLICIT NONE
    943951
    944     INTEGER(iwp) ::  i    !:
    945     INTEGER(iwp) ::  j    !:
    946     INTEGER(iwp) ::  k    !:
    947 
    948     REAL(wp)     ::  sbt  !:
     952    INTEGER(iwp) ::  i    !<
     953    INTEGER(iwp) ::  j    !<
     954    INTEGER(iwp) ::  k    !<
     955
     956    REAL(wp)     ::  sbt  !<
    949957
    950958
     
    17671775
    17681776
     1777!------------------------------------------------------------------------------!
     1778! Description:
     1779! ------------
     1780!> Version for accelerator boards
     1781!------------------------------------------------------------------------------!
     1782 
    17691783 SUBROUTINE prognostic_equations_acc
    17701784
    1771 !------------------------------------------------------------------------------!
    1772 ! Version for accelerator boards
    1773 !------------------------------------------------------------------------------!
    17741785
    17751786    IMPLICIT NONE
    17761787
    1777     INTEGER(iwp) ::  i           !:
    1778     INTEGER(iwp) ::  j           !:
    1779     INTEGER(iwp) ::  k           !:
    1780     INTEGER(iwp) ::  runge_step  !:
    1781 
    1782     REAL(wp)     ::  sbt         !:
     1788    INTEGER(iwp) ::  i           !<
     1789    INTEGER(iwp) ::  j           !<
     1790    INTEGER(iwp) ::  k           !<
     1791    INTEGER(iwp) ::  runge_step  !<
     1792
     1793    REAL(wp)     ::  sbt         !<
    17831794
    17841795!
Note: See TracChangeset for help on using the changeset viewer.