New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
phycst.F90 in NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/DOM – NEMO

source: NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/DOM/phycst.F90 @ 11615

Last change on this file since 11615 was 11615, checked in by laurent, 4 years ago

LB: new cool-skin and warm-layer parameterizations for ECMWF and COARE3.6, COARE3.0 uses same CSWL param as for COARE3.6.

  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE phycst
2   !!======================================================================
3   !!                    ***  MODULE  phycst  ***
4   !!     Definition of of both ocean and ice parameters used in the code
5   !!=====================================================================
6   !! History :   OPA  !  1990-10  (C. Levy - G. Madec)  Original code
7   !!             8.1  !  1991-11  (G. Madec, M. Imbard)  cosmetic changes
8   !!   NEMO      1.0  !  2002-08  (G. Madec, C. Ethe)  F90, add ice constants
9   !!              -   !  2006-08  (G. Madec)  style
10   !!             3.2  !  2006-08  (S. Masson, G. Madec)  suppress useless variables + style
11   !!             3.4  !  2011-11  (C. Harris)  minor changes for CICE constants
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   phy_cst  : define and print physical constant and domain parameters
16   !!----------------------------------------------------------------------
17   USE par_oce          ! ocean parameters
18   USE in_out_manager   ! I/O manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   phy_cst     ! routine called by inipar.F90
24
25   REAL(wp), PUBLIC ::   rpi      = 3.141592653589793_wp             !: pi
26   REAL(wp), PUBLIC ::   rad      = 3.141592653589793_wp / 180._wp   !: conversion from degre into radian
27   REAL(wp), PUBLIC ::   rsmall   = 0.5 * EPSILON( 1.e0 )            !: smallest real computer value
28   
29   REAL(wp), PUBLIC ::   rday     = 24.*60.*60.      !: day                                [s]
30   REAL(wp), PUBLIC ::   rsiyea                      !: sideral year                       [s]
31   REAL(wp), PUBLIC ::   rsiday                      !: sideral day                        [s]
32   REAL(wp), PUBLIC ::   raamo    =  12._wp          !: number of months in one year
33   REAL(wp), PUBLIC ::   rjjhh    =  24._wp          !: number of hours in one day
34   REAL(wp), PUBLIC ::   rhhmm    =  60._wp          !: number of minutes in one hour
35   REAL(wp), PUBLIC ::   rmmss    =  60._wp          !: number of seconds in one minute
36   REAL(wp), PUBLIC ::   omega                       !: earth rotation parameter           [s-1]
37   REAL(wp), PUBLIC ::   ra       = 6371229._wp      !: earth radius                       [m]
38   REAL(wp), PARAMETER, PUBLIC ::   grav     = 9.80665_wp       !: gravity                            [m/s2]    !LB
39   REAL(wp), PUBLIC ::   rt0      = 273.15_wp        !: freezing point of fresh water [Kelvin]
40
41   REAL(wp), PUBLIC ::   rau0                        !: volumic mass of reference     [kg/m3]
42   REAL(wp), PUBLIC ::   r1_rau0                     !: = 1. / rau0                   [m3/kg]
43   REAL(wp), PUBLIC ::   rcp                         !: ocean specific heat           [J/Kelvin]
44   REAL(wp), PUBLIC ::   r1_rcp                      !: = 1. / rcp                    [Kelvin/J]
45   REAL(wp), PUBLIC ::   rau0_rcp                    !: = rau0 * rcp
46   REAL(wp), PUBLIC ::   r1_rau0_rcp                 !: = 1. / ( rau0 * rcp )
47
48   REAL(wp), PUBLIC ::   emic     =    0.97_wp       !: emissivity of snow or ice (not used?)
49
50   REAL(wp), PUBLIC ::   sice     =    6.0_wp        !: salinity of ice (for pisces)          [psu]
51   REAL(wp), PUBLIC ::   soce     =   34.7_wp        !: salinity of sea (for pisces and isf)  [psu]
52   REAL(wp), PUBLIC ::   rLevap   =    2.46e+6_wp    !: latent heat of vaporization for sea-water   [J/kg] #LB
53   REAL(wp), PUBLIC ::   vkarmn   =    0.4_wp        !: von Karman constant
54   REAL(wp), PUBLIC ::   stefan   =    5.67e-8_wp    !: Stefan-Boltzmann constant
55
56   REAL(wp), PUBLIC ::   rhos     =  330._wp         !: volumic mass of snow                                  [kg/m3]
57   REAL(wp), PUBLIC ::   rhoi     =  917._wp         !: volumic mass of sea ice                               [kg/m3]
58   REAL(wp), PUBLIC ::   rhow     = 1000._wp         !: volumic mass of freshwater in melt ponds              [kg/m3]
59   REAL(wp), PUBLIC ::   rcnd_i   =    2.034396_wp   !: thermal conductivity of fresh ice                     [W/m/K]
60   REAL(wp), PUBLIC ::   rcpi     = 2067.0_wp        !: specific heat of fresh ice                            [J/kg/K]
61   REAL(wp), PUBLIC ::   rLsub    =    2.834e+6_wp   !: pure ice latent heat of sublimation                   [J/kg]
62   REAL(wp), PUBLIC ::   rLfus    =    0.334e+6_wp   !: latent heat of fusion of fresh ice                    [J/kg]
63   REAL(wp), PUBLIC ::   rTmlt    =    0.054_wp      !: decrease of seawater meltpoint with salinity
64
65   REAL(wp), PUBLIC ::   r1_rhoi                     !: 1 / rhoi
66   REAL(wp), PUBLIC ::   r1_rhos                     !: 1 / rhos
67   REAL(wp), PUBLIC ::   r1_rcpi                     !: 1 / rcpi
68
69
70   !#LB:
71   !! Mainly used in OCE/SBC (removed from sbcblk.F90)
72   REAL(wp), PARAMETER, PUBLIC :: rCp_dry = 1005.0_wp   !: Specic heat of dry air, constant pressure      [J/K/kg]
73   REAL(wp), PARAMETER, PUBLIC :: rCp_vap = 1860.0_wp   !: Specic heat of water vapor, constant pressure  [J/K/kg]
74   REAL(wp), PARAMETER, PUBLIC :: R_dry   = 287.05_wp   !: Specific gas constant for dry air              [J/K/kg]
75   REAL(wp), PARAMETER, PUBLIC :: R_vap   = 461.495_wp  !: Specific gas constant for water vapor          [J/K/kg]
76   REAL(wp), PARAMETER, PUBLIC :: reps0   = R_dry/R_vap !: ratio of gas constant for dry air and water vapor => ~ 0.622
77   REAL(wp), PARAMETER, PUBLIC :: rctv0   = R_vap/R_dry !: for virtual temperature (== (1-eps)/eps) => ~ 0.608
78   REAL(wp), PARAMETER, PUBLIC :: rCp_air = 1000.5_wp   !: specific heat of air (only used for ice fluxes now...)
79   REAL(wp), PARAMETER, PUBLIC :: rCd_ice = 1.4e-3_wp   !: transfer coefficient over ice
80   REAL(wp), PARAMETER, PUBLIC :: albo    = 0.066_wp    !: ocean albedo assumed to be constant
81   !
82   REAL(wp), PARAMETER, PUBLIC :: rho0_a  = 1.2_wp      !: Approx. of density of air                       [kg/m^3]
83   REAL(wp), PARAMETER, PUBLIC :: rho0_w  = 1025._wp    !: Density of sea-water  (ECMWF->1025)             [kg/m^3]
84   REAL(wp), PARAMETER, PUBLIC :: roadrw = rho0_a/rho0_w !: Density ratio
85   REAL(wp), PARAMETER, PUBLIC :: rCp0_w  = 4190._wp    !: Specific heat capacity of seawater (ECMWF 4190) [J/K/kg]
86   REAL(wp), PARAMETER, PUBLIC :: rnu0_w  = 1.e-6_wp    !: kinetic viscosity of water                      [m^2/s]
87   REAL(wp), PARAMETER, PUBLIC :: rk0_w   = 0.6_wp      !: thermal conductivity of water (at 20C)          [W/m/K]
88   !
89   REAL(wp), PARAMETER, PUBLIC :: emiss_w = 1._wp       !: Surface emissivity (black-body long-wave radiation) of sea-water []
90   !                                                    !: Theoretically close to 0.97! Yet, taken equal as 1 to account for
91   !                                                    !: the small fraction of downwelling shortwave reflected at the
92   !                                                    !: surface (Lind & Katsaros, 1986)
93   REAL(wp), PARAMETER, PUBLIC :: rdct_qsat_salt = 0.98_wp  !: reduction factor on specific humidity at saturation (q_sat(T_s)) due to salt
94   REAL(wp), PARAMETER, PUBLIC :: rtt0 = 273.16_wp        !: triple point of temperature    [K]
95   REAL(wp), PARAMETER, PUBLIC :: rcst_cs = 16._wp*grav*rho0_w*rCp0_w*rnu0_w*rnu0_w*rnu0_w/(rk0_w*rk0_w) !: for cool-skin parameterizations...
96   !#LB.
97
98
99   
100   !!----------------------------------------------------------------------
101   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
102   !! $Id$
103   !! Software governed by the CeCILL license (see ./LICENSE)
104   !!----------------------------------------------------------------------
105   
106CONTAINS
107   
108   SUBROUTINE phy_cst
109      !!----------------------------------------------------------------------
110      !!                       ***  ROUTINE phy_cst  ***
111      !!
112      !! ** Purpose :   set and print the constants
113      !!----------------------------------------------------------------------
114
115      rsiyea = 365.25_wp * rday * 2._wp * rpi / 6.283076_wp
116      rsiday = rday / ( 1._wp + rday / rsiyea )
117#if defined key_cice
118      omega  = 7.292116e-05
119#else
120      omega  = 2._wp * rpi / rsiday 
121#endif
122
123      r1_rhoi = 1._wp / rhoi
124      r1_rhos = 1._wp / rhos
125      r1_rcpi = 1._wp / rcpi
126
127      IF(lwp) THEN
128         WRITE(numout,*)
129         WRITE(numout,*) 'phy_cst : initialization of ocean parameters and constants'
130         WRITE(numout,*) '~~~~~~~'
131         WRITE(numout,*) '      mathematical constant                 rpi = ', rpi
132         WRITE(numout,*) '      day                                rday   = ', rday,   ' s'
133         WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s'
134         WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s'
135         WRITE(numout,*) '      omega                              omega  = ', omega,  ' s^-1'
136         WRITE(numout,*)
137         WRITE(numout,*) '      nb of months per year               raamo = ', raamo, ' months'
138         WRITE(numout,*) '      nb of hours per day                 rjjhh = ', rjjhh, ' hours'
139         WRITE(numout,*) '      nb of minutes per hour              rhhmm = ', rhhmm, ' mn'
140         WRITE(numout,*) '      nb of seconds per minute            rmmss = ', rmmss, ' s'
141         WRITE(numout,*)
142         WRITE(numout,*) '      earth radius                         ra   = ', ra   , ' m'
143         WRITE(numout,*) '      gravity                              grav = ', grav , ' m/s^2'
144         WRITE(numout,*)
145         WRITE(numout,*) '      freezing point of water              rt0  = ', rt0  , ' K'
146         WRITE(numout,*)
147         WRITE(numout,*) '   reference density and heat capacity now defined in eosbn2.f90'
148         WRITE(numout,*)
149         WRITE(numout,*) '      thermal conductivity of pure ice          = ', rcnd_i  , ' J/s/m/K'
150         WRITE(numout,*) '      thermal conductivity of snow is defined in a namelist '
151         WRITE(numout,*) '      fresh ice specific heat                   = ', rcpi    , ' J/kg/K'
152         WRITE(numout,*) '      latent heat of fusion of fresh ice / snow = ', rLfus   , ' J/kg'
153         WRITE(numout,*) '      latent heat of subl.  of fresh ice / snow = ', rLsub   , ' J/kg'
154         WRITE(numout,*) '      density of sea ice                        = ', rhoi    , ' kg/m^3'
155         WRITE(numout,*) '      density of snow                           = ', rhos    , ' kg/m^3'
156         WRITE(numout,*) '      density of freshwater (in melt ponds)     = ', rhow    , ' kg/m^3'
157         WRITE(numout,*) '      salinity of ice (for pisces)              = ', sice    , ' psu'
158         WRITE(numout,*) '      salinity of sea (for pisces and isf)      = ', soce    , ' psu'
159         WRITE(numout,*) '      latent heat of evaporation (water)        = ', rLevap  , ' J/m^3' 
160         WRITE(numout,*) '      von Karman constant                       = ', vkarmn 
161         WRITE(numout,*) '      Stefan-Boltzmann constant                 = ', stefan  , ' J/s/m^2/K^4'
162         WRITE(numout,*)
163         WRITE(numout,*) '      conversion: degre ==> radian          rad = ', rad
164         WRITE(numout,*)
165         WRITE(numout,*) '      smallest real computer value       rsmall = ', rsmall
166      ENDIF
167
168   END SUBROUTINE phy_cst
169
170   !!======================================================================
171END MODULE phycst
Note: See TracBrowser for help on using the repository browser.