Ignore:
Timestamp:
Apr 5, 2019 2:25:01 PM (5 years ago)
Author:
eckhard
Message:

inifor: Use PALM's working precision; improved error handling, coding style, and comments

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/UTIL/inifor/src/inifor_defs.f90

    r3801 r3866  
    2626! -----------------
    2727! $Id$
     28! Added parameter for INIFOR's log file name
     29! Use PALM's working precision
     30!
     31!
     32! 3801 2019-03-15 17:14:25Z eckhard
    2833! Defined netCDF variable names for COSMO grid
    2934! Bumped version number
     
    9499!> The defs module provides global constants used in INIFOR.
    95100!------------------------------------------------------------------------------!
    96 #if defined ( __netcdf )
    97101 MODULE inifor_defs
    98102 
     103 USE kinds,                                                                    &
     104     ONLY :  wp, iwp
     105
    99106 IMPLICIT NONE
    100107
    101108!
    102109!-- Parameters for type definitions
    103  INTEGER, PARAMETER  ::  dp    = 8   !< double precision (8 bytes = 64 bits)
    104  INTEGER, PARAMETER  ::  sp    = 4   !< single precision (4 bytes = 32 bits)
    105  INTEGER, PARAMETER  ::  hp    = 2   !< half precision (2 bytes = 16 bits)
    106110 INTEGER, PARAMETER  ::  PATH  = 140 !< length of file path strings
    107111 INTEGER, PARAMETER  ::  LNAME = 150 !< length of long name strings
     
    111115!
    112116!-- Trigonomentry
    113  REAL(dp), PARAMETER ::  PI = 3.14159265358979323846264338_dp !< Ratio of a circle's circumference to its diamter [-]
    114  REAL(dp), PARAMETER ::  TO_RADIANS = PI / 180.0_dp           !< Conversion factor from degrees to radiant [-]
    115  REAL(dp), PARAMETER ::  TO_DEGREES = 180.0_dp / PI           !< Conversion factor from radians to degrees [-]
     117 REAL(wp), PARAMETER ::  PI = 3.14159265358979323846264338_wp !< Ratio of a circle's circumference to its diamter [-]
     118 REAL(wp), PARAMETER ::  TO_RADIANS = PI / 180.0_wp           !< Conversion factor from degrees to radiant [-]
     119 REAL(wp), PARAMETER ::  TO_DEGREES = 180.0_wp / PI           !< Conversion factor from radians to degrees [-]
    116120
    117121!
    118122!-- COSMO parameters
    119123 INTEGER, PARAMETER  ::  WATER_ID = 9                !< Integer corresponding to the water soil type in COSMO-DE [-]
    120  REAL(dp), PARAMETER ::  EARTH_RADIUS = 6371229.0_dp !< Earth radius used in COSMO-DE [m]
    121  REAL(dp), PARAMETER ::  P_SL = 1e5_dp               !< Reference pressure for computation of COSMO-DE's basic state pressure [Pa]
    122  REAL(dp), PARAMETER ::  T_SL = 288.15_dp            !< Reference temperature for computation of COSMO-DE's basic state pressure [K]
    123  REAL(dp), PARAMETER ::  BETA = 42.0_dp              !< logarithmic lapse rate, dT / d ln(p), for computation of COSMO-DE's basic
     124 REAL(wp), PARAMETER ::  EARTH_RADIUS = 6371229.0_wp !< Earth radius used in COSMO-DE [m]
     125 REAL(wp), PARAMETER ::  P_SL = 1e5_wp               !< Reference pressure for computation of COSMO-DE's basic state pressure [Pa]
     126 REAL(wp), PARAMETER ::  T_SL = 288.15_wp            !< Reference temperature for computation of COSMO-DE's basic state pressure [K]
     127 REAL(wp), PARAMETER ::  BETA = 42.0_wp              !< logarithmic lapse rate, dT / d ln(p), for computation of COSMO-DE's basic
    124128                                                     !< state pressure [K]
    125  REAL(dp), PARAMETER ::  RD   = 287.05_dp            !< specific gas constant of dry air, used in computation of COSMO-DE's basic
     129 REAL(wp), PARAMETER ::  RD   = 287.05_wp            !< specific gas constant of dry air, used in computation of COSMO-DE's basic
    126130                                                     !< state [J/kg/K]
    127  REAL(dp), PARAMETER ::  RV   = 461.51_dp            !< specific gas constant of water vapor [J/kg/K]
    128  REAL(dp), PARAMETER ::  G    = 9.80665_dp           !< acceleration of Earth's gravity, used in computation of COSMO-DE's basic
     131 REAL(wp), PARAMETER ::  RV   = 461.51_wp            !< specific gas constant of water vapor [J/kg/K]
     132 REAL(wp), PARAMETER ::  G    = 9.80665_wp           !< acceleration of Earth's gravity, used in computation of COSMO-DE's basic
    129133                                                     !< state [m/s/s]
    130  REAL(dp), PARAMETER ::  RHO_L = 1e3_dp              !< density of liquid water, used to convert W_SO from [kg/m^2] to [m^3/m^3],
     134 REAL(wp), PARAMETER ::  RHO_L = 1e3_wp              !< density of liquid water, used to convert W_SO from [kg/m^2] to [m^3/m^3],
    131135                                                     !< in [kg/m^3]
    132  REAL(dp), PARAMETER ::  HECTO = 100_dp              !< unit conversion factor from hPa to Pa
     136 REAL(wp), PARAMETER ::  HECTO = 100_wp              !< unit conversion factor from hPa to Pa
    133137
    134138!
    135139!-- PALM-4U parameters
    136  REAL(dp), PARAMETER ::  OMEGA   = 7.29e-5_dp !< angular velocity of Earth's rotation [s^-1]
    137  REAL(dp), PARAMETER ::  P_REF   = 1e5_dp     !< Reference pressure for potential temperature [Pa]
    138  REAL(dp), PARAMETER ::  RD_PALM = 287.0_dp   !< specific gas constant of dry air, used in computation of PALM-4U's potential temperature [J/kg/K]
    139  REAL(dp), PARAMETER ::  CP_PALM = 1005.0_dp  !< heat capacity of dry air at constant pressure, used in computation of PALM-4U's potential temperature [J/kg/K]
     140 REAL(wp), PARAMETER ::  OMEGA   = 7.29e-5_wp !< angular velocity of Earth's rotation [s^-1]
     141 REAL(wp), PARAMETER ::  P_REF   = 1e5_wp     !< Reference pressure for potential temperature [Pa]
     142 REAL(wp), PARAMETER ::  RD_PALM = 287.0_wp   !< specific gas constant of dry air, used in computation of PALM-4U's potential temperature [J/kg/K]
     143 REAL(wp), PARAMETER ::  CP_PALM = 1005.0_wp  !< heat capacity of dry air at constant pressure, used in computation of PALM-4U's potential temperature [J/kg/K]
    140144
    141145!
     
    154158                                                              !< water cells [-]
    155159 INTEGER, PARAMETER          ::  FORCING_STEP = 1             !< Number of hours between forcing time steps [h]
    156  REAL(dp), PARAMETER         ::  NUDGING_TAU = 21600.0_dp     !< Nudging relaxation time scale [s]
    157  CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.8'            !< INIFOR version number
     160 REAL(wp), PARAMETER         ::  NUDGING_TAU = 21600.0_wp     !< Nudging relaxation time scale [s]
    158161 CHARACTER(LEN=*), PARAMETER ::  COPYRIGHT = 'Copyright 2017-2019 Leibniz Universitaet Hannover' // &
    159      ACHAR( 10 ) // ' Copyright 2017-2019 Deutscher Wetterdienst Offenbach' !< Copyright notice
    160 
     162    ACHAR( 10 ) // ' Copyright 2017-2019 Deutscher Wetterdienst Offenbach' !< Copyright notice
     163 CHARACTER(LEN=*), PARAMETER ::  LOG_FILE_NAME = 'inifor.log' !< Name of INIFOR's log file
     164 CHARACTER(LEN=*), PARAMETER ::  VERSION = '1.4.9rc'          !< INIFOR version number
     165 
    161166 END MODULE inifor_defs
    162 #endif
Note: See TracChangeset for help on using the changeset viewer.