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

    r1354 r1682  
    1  MODULE eqn_state_seawater_mod
    2 
     1!> @file eqn_state_seawater.f90
    32!------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4645! Description:
    4746! ------------
    48 ! Equation of state for seawater as a function of potential temperature,
    49 ! salinity, and pressure.
    50 ! For coefficients see Jackett et al., 2006: J. Atm. Ocean Tech.
    51 ! eqn_state_seawater calculates the potential density referred at hyp(0).
    52 ! eqn_state_seawater_func calculates density.
    53 !------------------------------------------------------------------------------!
     47!> Equation of state for seawater as a function of potential temperature,
     48!> salinity, and pressure.
     49!> For coefficients see Jackett et al., 2006: J. Atm. Ocean Tech.
     50!> eqn_state_seawater calculates the potential density referred at hyp(0).
     51!> eqn_state_seawater_func calculates density.
     52!------------------------------------------------------------------------------!
     53 MODULE eqn_state_seawater_mod
     54 
    5455   
    5556    USE kinds
     
    6768                             9.8920219266399117D-8,  4.6996642771754730D-6,    &
    6869                            -2.5862187075154352D-8, -3.2921414007960662D-12 /)
    69                           !:
     70                          !<
    7071
    7172    REAL(wp), DIMENSION(13), PARAMETER ::  den =                               &
     
    7778                             6.7103246285651894D-6, -2.4461698007024582D-17,   &
    7879                            -9.1534417604289062D-18 /)
    79                           !:
     80                          !<
    8081
    8182    INTERFACE eqn_state_seawater
     
    9293
    9394!------------------------------------------------------------------------------!
    94 ! Call for all grid points
     95! Description:
     96! ------------
     97!> Call for all grid points
    9598!------------------------------------------------------------------------------!
    9699    SUBROUTINE eqn_state_seawater
     
    103106       IMPLICIT NONE
    104107
    105        INTEGER(iwp) ::  i  !:
    106        INTEGER(iwp) ::  j  !:
    107        INTEGER(iwp) ::  k  !:
    108 
    109        REAL(wp) ::  pden  !:
    110        REAL(wp) ::  pnom  !:
    111        REAL(wp) ::  p1    !:
    112        REAL(wp) ::  p2    !:
    113        REAL(wp) ::  p3    !:
    114        REAL(wp) ::  pt1   !:
    115        REAL(wp) ::  pt2   !:
    116        REAL(wp) ::  pt3   !:
    117        REAL(wp) ::  pt4   !:
    118        REAL(wp) ::  sa1   !:
    119        REAL(wp) ::  sa15  !:
    120        REAL(wp) ::  sa2   !:
     108       INTEGER(iwp) ::  i  !<
     109       INTEGER(iwp) ::  j  !<
     110       INTEGER(iwp) ::  k  !<
     111
     112       REAL(wp) ::  pden  !<
     113       REAL(wp) ::  pnom  !<
     114       REAL(wp) ::  p1    !<
     115       REAL(wp) ::  p2    !<
     116       REAL(wp) ::  p3    !<
     117       REAL(wp) ::  pt1   !<
     118       REAL(wp) ::  pt2   !<
     119       REAL(wp) ::  pt3   !<
     120       REAL(wp) ::  pt4   !<
     121       REAL(wp) ::  sa1   !<
     122       REAL(wp) ::  sa15  !<
     123       REAL(wp) ::  sa2   !<
    121124       
    122125                       
     
    180183
    181184!------------------------------------------------------------------------------!
    182 ! Call for grid point i,j
     185! Description:
     186! ------------
     187!> Call for grid point i,j
    183188!------------------------------------------------------------------------------!
    184189    SUBROUTINE eqn_state_seawater_ij( i, j )
     
    251256
    252257!------------------------------------------------------------------------------!
    253 ! Equation of state as a function
     258! Description:
     259! ------------
     260!> Equation of state as a function
    254261!------------------------------------------------------------------------------!
    255262    REAL(wp) FUNCTION eqn_state_seawater_func( p, pt, sa )
     
    257264       IMPLICIT NONE
    258265
    259        REAL(wp) ::  p      !:
    260        REAL(wp) ::  p1     !:
    261        REAL(wp) ::  p2     !:
    262        REAL(wp) ::  p3     !:
    263        REAL(wp) ::  pt     !:
    264        REAL(wp) ::  pt1    !:
    265        REAL(wp) ::  pt2    !:
    266        REAL(wp) ::  pt3    !:
    267        REAL(wp) ::  pt4    !:
    268        REAL(wp) ::  sa     !:
    269        REAL(wp) ::  sa15   !:
    270        REAL(wp) ::  sa2    !:
     266       REAL(wp) ::  p      !<
     267       REAL(wp) ::  p1     !<
     268       REAL(wp) ::  p2     !<
     269       REAL(wp) ::  p3     !<
     270       REAL(wp) ::  pt     !<
     271       REAL(wp) ::  pt1    !<
     272       REAL(wp) ::  pt2    !<
     273       REAL(wp) ::  pt3    !<
     274       REAL(wp) ::  pt4    !<
     275       REAL(wp) ::  sa     !<
     276       REAL(wp) ::  sa15   !<
     277       REAL(wp) ::  sa2    !<
    271278
    272279!
Note: See TracChangeset for help on using the changeset viewer.