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

    r1552 r1682  
    1  SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
    2 
     1!> @file user_data_output_3d.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4746! Description:
    4847! ------------
    49 ! Resorts the user-defined output quantity with indices (k,j,i) to a
    50 ! temporary array with indices (i,j,k).
     48!> Resorts the user-defined output quantity with indices (k,j,i) to a
     49!> temporary array with indices (i,j,k).
    5150!------------------------------------------------------------------------------!
     51 SUBROUTINE user_data_output_3d( av, variable, found, local_pf, nzb_do, nzt_do )
     52 
    5253
    5354    USE indices
     
    5960    IMPLICIT NONE
    6061
    61     CHARACTER (LEN=*) ::  variable !:
     62    CHARACTER (LEN=*) ::  variable !<
    6263
    63     INTEGER(iwp) ::  av    !:
    64     INTEGER(iwp) ::  i     !:
    65     INTEGER(iwp) ::  j     !:
    66     INTEGER(iwp) ::  k     !:
    67     INTEGER(iwp) ::  nzb_do !: lower limit of the data output (usually 0)
    68     INTEGER(iwp) ::  nzt_do !: vertical upper limit of the data output (usually nz_do3d)
     64    INTEGER(iwp) ::  av    !<
     65    INTEGER(iwp) ::  i     !<
     66    INTEGER(iwp) ::  j     !<
     67    INTEGER(iwp) ::  k     !<
     68    INTEGER(iwp) ::  nzb_do !< lower limit of the data output (usually 0)
     69    INTEGER(iwp) ::  nzt_do !< vertical upper limit of the data output (usually nz_do3d)
    6970
    70     LOGICAL      ::  found !:
     71    LOGICAL      ::  found !<
    7172
    72    REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) ::  local_pf !:
     73   REAL(sp), DIMENSION(nxlg:nxrg,nysg:nyng,nzb_do:nzt_do) ::  local_pf !<
    7374
    7475
Note: See TracChangeset for help on using the changeset viewer.