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/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DOM – NEMO

source: NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DOM/phycst.F90 @ 9939

Last change on this file since 9939 was 9939, checked in by gm, 6 years ago

#1911 (ENHANCE-04): RK3 branche phased with MLF@9937 branche

  • Property svn:keywords set to Id
File size: 8.7 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), PUBLIC ::   grav  = 9.80665_wp     !: gravity                                [m/s2]
39   
40   REAL(wp), PUBLIC ::   rt0      = 273.15_wp        !: freezing point of fresh water     [Kelvin]
41   REAL(wp), PUBLIC ::   rho0                        !: volumic mass of reference         [kg/m3]
42   REAL(wp), PUBLIC ::   r1_rho0                     !: = 1. / rho0                       [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 ::   rho0_rcp                    !: = rho0 * rcp
46   REAL(wp), PUBLIC ::   r1_rho0_rcp                 !: = 1. / ( rho0 * rcp )
47
48   REAL(wp), PUBLIC ::   rhoi     =  917._wp         !: sea ice density                   [kg/m3]
49   REAL(wp), PUBLIC ::   rhos     =  330._wp         !: snow    density                   [kg/m3]
50   REAL(wp), PUBLIC ::   rhow     = 1000._wp         !: water   density (in melt ponds)   [kg/m3]
51   REAL(wp), PUBLIC ::   rcnd_i   =    2.034396_wp   !: thermal conductivity of fresh ice [W/m/K]
52   REAL(wp), PUBLIC ::   rcpi     = 2067.0_wp        !: specific heat of fresh ice        [J/kg/K]
53   REAL(wp), PUBLIC ::   rLsub    =    2.834e+6_wp   !: pure ice latent heat of sublimation   [J/kg]
54   REAL(wp), PUBLIC ::   rLfus    =    0.334e+6_wp   !: latent heat of fusion of fresh ice    [J/kg]
55   REAL(wp), PUBLIC ::   tmut     =    0.054_wp      !: decrease of seawater meltpoint with salinity
56   REAL(wp), PUBLIC ::   emic     =    0.97_wp       !: emissivity of snow or ice
57   REAL(wp), PUBLIC ::   sice     =    6.0_wp        !: salinity of ice                   [psu]
58   REAL(wp), PUBLIC ::   soce     =   34.7_wp        !: salinity of sea                   [psu]
59   REAL(wp), PUBLIC ::   vkarmn   =    0.4_wp        !: von Karman constant
60   REAL(wp), PUBLIC ::   stefan   =    5.67e-8_wp    !: Stefan-Boltzmann constant
61
62   REAL(wp), PUBLIC ::   r1_rhoi                     !: 1 / rhoi
63   REAL(wp), PUBLIC ::   r1_rhos                     !: 1 / rhos
64   REAL(wp), PUBLIC ::   r1_rhow                     !: 1 / rhow
65   REAL(wp), PUBLIC ::   r1_cpi                      !: 1 / rcpi
66   REAL(wp), PUBLIC ::   r1_Lsub                     !: 1 / rLsub
67   REAL(wp), PUBLIC ::   r1_Lfus                     !: 1 / rLfus
68
69   !!----------------------------------------------------------------------
70   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
71   !! $Id$
72   !! Software governed by the CeCILL licence (./LICENSE)
73   !!----------------------------------------------------------------------
74   
75CONTAINS
76   
77   SUBROUTINE phy_cst
78      !!----------------------------------------------------------------------
79      !!                       ***  ROUTINE phy_cst  ***
80      !!
81      !! ** Purpose :   set and print the constants
82      !!----------------------------------------------------------------------
83      !
84      IF(lwp) WRITE(numout,*)
85      IF(lwp) WRITE(numout,*) 'phy_cst : initialization of ocean parameters and constants'
86      IF(lwp) WRITE(numout,*) '~~~~~~~'
87
88      !                 !==  Define derived constant  ==!
89
90      rsiyea = 365.25_wp * rday * 2._wp * rpi / 6.283076_wp
91      rsiday = rday / ( 1._wp + rday / rsiyea )
92#if defined key_cice
93      omega  = 7.292116e-05
94#else
95      omega  = 2._wp * rpi / rsiday 
96#endif
97
98      r1_rhoi = 1._wp / rhoi
99      r1_rhos = 1._wp / rhos
100      r1_cpi  = 1._wp / rcpi
101      r1_Lsub = 1._wp / rLsub
102      r1_Lfus = 1._wp / rLfus
103
104      IF(lwp) THEN      !==  print constants  ==!
105         WRITE(numout,*)
106         WRITE(numout,*) '   Constants'
107         WRITE(numout,*)
108         WRITE(numout,*) '      mathematical constant              rpi    = ', rpi
109         WRITE(numout,*) '      conversion: degre ==> radian       rad    = ', rad
110         WRITE(numout,*)
111         WRITE(numout,*) '      day in seconds                     rday   = ', rday  , ' s'
112         WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s'
113         WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s'
114         WRITE(numout,*) '      omega = 2 pi / rsiday              omega  = ', omega , ' s^-1'
115         WRITE(numout,*) '      earth radius                       ra     = ', ra    , ' m'
116         WRITE(numout,*) '      gravity                            grav   = ', grav  , ' m/s^2'
117         WRITE(numout,*)
118         WRITE(numout,*) '      nb of months per year              raamo  = ', raamo, ' months'
119         WRITE(numout,*) '      nb of hours per day                rjjhh  = ', rjjhh, ' hours'
120         WRITE(numout,*) '      nb of minutes per hour             rhhmm  = ', rhhmm, ' mn'
121         WRITE(numout,*) '      nb of seconds per minute           rmmss  = ', rmmss, ' s'
122         WRITE(numout,*)
123         WRITE(numout,*) '   reference ocean density and heat capacity now defined in eosbn2.f90'
124         WRITE(numout,*)
125         WRITE(numout,*) '      freezing point of freshwater                rt0    = ', rt0   , ' K'
126         WRITE(numout,*) '      sea ice density                             rhoi   = ', rhoi  , ' kg/m^3'
127         WRITE(numout,*) '      snow    density                             rhos   = ', rhos  , ' kg/m^3'
128         WRITE(numout,*) '      freshwater density (in melt ponds)          rhow   = ', rhow  , ' kg/m^3'
129         WRITE(numout,*) '      thermal conductivity of pure ice            rcnd_i = ', rcnd_i, ' J/s/m/K'
130         WRITE(numout,*) '      fresh ice specific heat                     rcpi   = ', rcpi  , ' J/kg/K'
131         WRITE(numout,*) '      latent heat of fusion of fresh ice / snow   rLfus  = ', rLfus , ' J/kg'
132         WRITE(numout,*) '      latent heat of subl.  of fresh ice / snow   rLsub  = ', rLsub , ' J/kg'
133         WRITE(numout,*) '      emissivity of snow or ice                   emic   = ', emic 
134         WRITE(numout,*) '      salinity of ice                             sice   = ', sice  , ' psu'
135         WRITE(numout,*) '      salinity of sea                             soce   = ', soce  , ' psu'
136         WRITE(numout,*) '      von Karman constant                         vkarmn = ', vkarmn 
137         WRITE(numout,*) '      Stefan-Boltzmann constant                   stefan = ', stefan, ' J/s/m^2/K^4'
138         WRITE(numout,*)
139         WRITE(numout,*)
140         WRITE(numout,*) '      smallest real computer value                rsmall = ', rsmall
141      ENDIF
142      !
143   END SUBROUTINE phy_cst
144
145   !!======================================================================
146END MODULE phycst
Note: See TracBrowser for help on using the repository browser.