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

    r1320 r1682  
    1  MODULE kinds
    2 
     1!> @file mod_kinds.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    3130! Description:
    3231! ------------
    33 ! Standard kind definitions
    34 ! wp (working precision) and iwp (integer working precision) are the kinds
    35 ! used by default in all variable declarations.
    36 ! By default, PALM is using wp = dp (64bit), and iwp = isp (32bit).
    37 ! If you like to switch to other precision, then please set wp/iwp
    38 ! appropriately by assigning other kinds below.
     32!> Standard kind definitions
     33!> wp (working precision) and iwp (integer working precision) are the kinds
     34!> used by default in all variable declarations.
     35!> By default, PALM is using wp = dp (64bit), and iwp = isp (32bit).
     36!> If you like to switch to other precision, then please set wp/iwp
     37!> appropriately by assigning other kinds below.
    3938!------------------------------------------------------------------------------!
     39 MODULE kinds
     40 
    4041
    4142    IMPLICIT NONE
     
    4344!
    4445!-- Floating point kinds
    45     INTEGER, PARAMETER ::  sp = 4           !: single precision (32 bit)
    46     INTEGER, PARAMETER ::  dp = 8           !: double precision (64 bit)
     46    INTEGER, PARAMETER ::  sp = 4           !< single precision (32 bit)
     47    INTEGER, PARAMETER ::  dp = 8           !< double precision (64 bit)
    4748
    4849!
    4950!-- Integer kinds
    50     INTEGER, PARAMETER ::  isp = SELECTED_INT_KIND(  9 )   !: single precision (32 bit)
    51     INTEGER, PARAMETER ::  idp = SELECTED_INT_KIND( 14 )   !: double precision (64 bit)
     51    INTEGER, PARAMETER ::  isp = SELECTED_INT_KIND(  9 )   !< single precision (32 bit)
     52    INTEGER, PARAMETER ::  idp = SELECTED_INT_KIND( 14 )   !< double precision (64 bit)
    5253
    5354!
    5455!-- Set kinds to be used as defaults
    55     INTEGER, PARAMETER ::   wp =  dp          !: default real kind
    56     INTEGER, PARAMETER ::  iwp = isp          !: default integer kind
     56    INTEGER, PARAMETER ::   wp =  dp          !< default real kind
     57    INTEGER, PARAMETER ::  iwp = isp          !< default integer kind
    5758
    5859    SAVE
Note: See TracChangeset for help on using the changeset viewer.