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

    r1428 r1682  
    1  SUBROUTINE surface_coupler
    2 
     1!> @file surface_coupler.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6867! Description:
    6968! ------------
    70 ! Data exchange at the interface between coupled models
     69!> Data exchange at the interface between coupled models
    7170!------------------------------------------------------------------------------!
     71 SUBROUTINE surface_coupler
     72 
    7273
    7374    USE arrays_3d,                                                             &
     
    9697    IMPLICIT NONE
    9798
    98     REAL(wp)    ::  time_since_reference_point_rem        !:
    99     REAL(wp)    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp) !:
    100 
    101     REAL(wp)    ::  cpw = 4218.0_wp !: heat capacity of water at constant pressure
     99    REAL(wp)    ::  time_since_reference_point_rem        !<
     100    REAL(wp)    ::  total_2d(-nbgp:ny+nbgp,-nbgp:nx+nbgp) !<
     101
     102    REAL(wp)    ::  cpw = 4218.0_wp !< heat capacity of water at constant pressure
    102103
    103104#if defined( __parallel )
     
    441442
    442443
     444!------------------------------------------------------------------------------!
     445! Description:
     446! ------------
     447!> @todo Missing subroutine description.
     448!------------------------------------------------------------------------------!
    443449  SUBROUTINE interpolate_to_atmos( tag )
    444450
     
    457463    IMPLICIT NONE
    458464
    459     INTEGER(iwp) ::  dnx  !:
    460     INTEGER(iwp) ::  dnx2 !:
    461     INTEGER(iwp) ::  dny  !:
    462     INTEGER(iwp) ::  dny2 !:
    463     INTEGER(iwp) ::  i    !:
    464     INTEGER(iwp) ::  ii   !:
    465     INTEGER(iwp) ::  j    !:
    466     INTEGER(iwp) ::  jj   !:
    467 
    468     INTEGER(iwp), intent(in) ::  tag !:
     465    INTEGER(iwp) ::  dnx  !<
     466    INTEGER(iwp) ::  dnx2 !<
     467    INTEGER(iwp) ::  dny  !<
     468    INTEGER(iwp) ::  dny2 !<
     469    INTEGER(iwp) ::  i    !<
     470    INTEGER(iwp) ::  ii   !<
     471    INTEGER(iwp) ::  j    !<
     472    INTEGER(iwp) ::  jj   !<
     473
     474    INTEGER(iwp), intent(in) ::  tag !<
    469475
    470476    CALL MPI_BARRIER( comm2d, ierr )
     
    525531
    526532
     533!------------------------------------------------------------------------------!
     534! Description:
     535! ------------
     536!> @todo Missing subroutine description.
     537!------------------------------------------------------------------------------!
    527538  SUBROUTINE interpolate_to_ocean( tag )
    528539
     
    541552    IMPLICIT NONE
    542553
    543     INTEGER(iwp)             ::  dnx !:
    544     INTEGER(iwp)             ::  dny !:
    545     INTEGER(iwp)             ::  i   !:
    546     INTEGER(iwp)             ::  ii  !:
    547     INTEGER(iwp)             ::  j   !:
    548     INTEGER(iwp)             ::  jj  !:
    549     INTEGER(iwp), intent(in) ::  tag !:
    550 
    551     REAL(wp)                 ::  fl  !:
    552     REAL(wp)                 ::  fr  !:
    553     REAL(wp)                 ::  myl !:
    554     REAL(wp)                 ::  myr !:
     554    INTEGER(iwp)             ::  dnx !<
     555    INTEGER(iwp)             ::  dny !<
     556    INTEGER(iwp)             ::  i   !<
     557    INTEGER(iwp)             ::  ii  !<
     558    INTEGER(iwp)             ::  j   !<
     559    INTEGER(iwp)             ::  jj  !<
     560    INTEGER(iwp), intent(in) ::  tag !<
     561
     562    REAL(wp)                 ::  fl  !<
     563    REAL(wp)                 ::  fr  !<
     564    REAL(wp)                 ::  myl !<
     565    REAL(wp)                 ::  myr !<
    555566
    556567    CALL MPI_BARRIER( comm2d, ierr )
Note: See TracChangeset for help on using the changeset viewer.