1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980818283848586878889909192939495 |
- MODULE phycst
- !!======================================================================
- !! *** MODULE phycst ***
- !! Definition of of both ocean and ice parameters used in the code
- !!=====================================================================
- !! History : OPA ! 1990-10 (C. Levy - G. Madec) Original code
- !! 8.1 ! 1991-11 (G. Madec, M. Imbard) cosmetic changes
- !! NEMO 1.0 ! 2002-08 (G. Madec, C. Ethe) F90, add ice constants
- !! - ! 2006-08 (G. Madec) style
- !! 3.2 ! 2006-08 (S. Masson, G. Madec) suppress useless variables + style
- !!----------------------------------------------------------------------
- !!----------------------------------------------------------------------
- !! phy_cst : define and print physical constant and domain parameters
- !!----------------------------------------------------------------------
- use par_kind
- IMPLICIT NONE
- PRIVATE
- PUBLIC phy_cst ! routine called by inipar.F90
- REAL(wp), PUBLIC :: rpi = 3.141592653589793_wp !: pi
- REAL(wp), PUBLIC :: rad = 3.141592653589793_wp / 180._wp !: conversion from degre into radian
- REAL(wp), PUBLIC :: rsmall = 0.5 * EPSILON( 1.e0 ) !: smallest real computer value
-
- REAL(wp), PUBLIC :: rday = 24.*60.*60. !: day (s)
- REAL(wp), PUBLIC :: rsiyea !: sideral year (s)
- REAL(wp), PUBLIC :: rsiday !: sideral day (s)
- REAL(wp), PUBLIC :: raamo = 12._wp !: number of months in one year
- REAL(wp), PUBLIC :: rjjhh = 24._wp !: number of hours in one day
- REAL(wp), PUBLIC :: rhhmm = 60._wp !: number of minutes in one hour
- REAL(wp), PUBLIC :: rmmss = 60._wp !: number of seconds in one minute
- !! REAL(wp), PUBLIC :: omega = 7.292115083046061e-5_wp , & !: change the last digit!
- REAL(wp), PUBLIC :: omega !: earth rotation parameter
- REAL(wp), PUBLIC :: ra = 6371229._wp !: earth radius (meter)
- REAL(wp), PUBLIC :: grav = 9.80665_wp !: gravity (m/s2)
-
- REAL(wp), PUBLIC :: rtt = 273.16_wp !: triple point of temperature (Kelvin)
- REAL(wp), PUBLIC :: rt0 = 273.15_wp !: freezing point of water (Kelvin)
- REAL(wp), PUBLIC :: rt0_snow = 273.15_wp !: melting point of snow (Kelvin)
- REAL(wp), PUBLIC :: rt0_ice = 273.05_wp !: melting point of ice (Kelvin)
- REAL(wp), PUBLIC :: rau0 = 1020._wp !: reference volumic mass (density) (kg/m3)
- REAL(wp), PUBLIC :: rau0r !: reference specific volume (m3/kg)
- REAL(wp), PUBLIC :: rcp = 4.e+3_wp !: ocean specific heat
- REAL(wp), PUBLIC :: ro0cpr !: = 1. / ( rau0 * rcp )
- REAL(wp), PUBLIC :: rcdsn = 0.22_wp !: conductivity of the snow
- REAL(wp), PUBLIC :: rcdic = 2.034396_wp !: conductivity of the ice
- REAL(wp), PUBLIC :: rcpsn = 6.9069e+5_wp !: density times specific heat for snow
- REAL(wp), PUBLIC :: rcpic = 1.8837e+6_wp !: volumetric latent heat fusion of sea ice
- REAL(wp), PUBLIC :: xlsn = 110.121e+6_wp !: volumetric latent heat fusion of snow
- REAL(wp), PUBLIC :: xlic = 300.33e+6_wp !: volumetric latent heat fusion of ice
- REAL(wp), PUBLIC :: xsn = 2.8e+6 !: latent heat of sublimation of snow
- REAL(wp), PUBLIC :: rhoic = 900._wp !: volumic mass of sea ice (kg/m3)
- REAL(wp), PUBLIC :: rhosn = 330._wp !: volumic mass of snow (kg/m3)
- REAL(wp), PUBLIC :: emic = 0.97_wp !: emissivity of snow or ice
- REAL(wp), PUBLIC :: sice = 6.0_wp !: reference salinity of ice (psu)
- REAL(wp), PUBLIC :: soce = 34.7_wp !: reference salinity of sea (psu)
- REAL(wp), PUBLIC :: cevap = 2.5e+6_wp !: latent heat of evaporation (water)
- REAL(wp), PUBLIC :: srgamma = 0.9_wp !: correction factor for solar radiation (Oberhuber, 1974)
- REAL(wp), PUBLIC :: vkarmn = 0.4_wp !: von Karman constant
- REAL(wp), PUBLIC :: stefan = 5.67e-8_wp !: Stefan-Boltzmann constant
- !!----------------------------------------------------------------------
- !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
- !! $Id: phycst.F90 1932 2010-06-15 10:28:20Z smasson $
- !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
- !!----------------------------------------------------------------------
-
- CONTAINS
-
- SUBROUTINE phy_cst
- !!----------------------------------------------------------------------
- !! *** ROUTINE phy_cst ***
- !!
- !! ** Purpose : Print model parameters and set and print the constants
- !!----------------------------------------------------------------------
- CHARACTER (len=64) :: cform = "(A12, 3(A13, I7) )"
- !!----------------------------------------------------------------------
- ! ! Define additional parameters
- rsiyea = 365.25 * rday * 2. * rpi / 6.283076
- rsiday = rday / ( 1. + rday / rsiyea )
- omega = 2. * rpi / rsiday
- rau0r = 1. / rau0
- ro0cpr = 1. / ( rau0 * rcp )
- END SUBROUTINE phy_cst
- !!======================================================================
- END MODULE phycst
|