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/UKMO/dev_r10448_bdyvol/src/OCE/DOM – NEMO

source: NEMO/branches/UKMO/dev_r10448_bdyvol/src/OCE/DOM/phycst.F90 @ 10455

Last change on this file since 10455 was 10068, checked in by nicolasmartin, 6 years ago

First part of modifications to have a common default header : fix typos and SVN keywords properties

  • Property svn:keywords set to Id
File size: 8.5 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   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.5e+6_wp     !: latent heat of evaporation (water)
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   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
70   !! $Id$
71   !! Software governed by the CeCILL license (see ./LICENSE)
72   !!----------------------------------------------------------------------
73   
74CONTAINS
75   
76   SUBROUTINE phy_cst
77      !!----------------------------------------------------------------------
78      !!                       ***  ROUTINE phy_cst  ***
79      !!
80      !! ** Purpose :   set and print the constants
81      !!----------------------------------------------------------------------
82
83      rsiyea = 365.25_wp * rday * 2._wp * rpi / 6.283076_wp
84      rsiday = rday / ( 1._wp + rday / rsiyea )
85#if defined key_cice
86      omega  = 7.292116e-05
87#else
88      omega  = 2._wp * rpi / rsiday 
89#endif
90
91      r1_rhoi = 1._wp / rhoi
92      r1_rhos = 1._wp / rhos
93      r1_rcpi = 1._wp / rcpi
94
95      IF(lwp) THEN
96         WRITE(numout,*)
97         WRITE(numout,*) 'phy_cst : initialization of ocean parameters and constants'
98         WRITE(numout,*) '~~~~~~~'
99         WRITE(numout,*) '      mathematical constant                 rpi = ', rpi
100         WRITE(numout,*) '      day                                rday   = ', rday,   ' s'
101         WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s'
102         WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s'
103         WRITE(numout,*) '      omega                              omega  = ', omega,  ' s^-1'
104         WRITE(numout,*)
105         WRITE(numout,*) '      nb of months per year               raamo = ', raamo, ' months'
106         WRITE(numout,*) '      nb of hours per day                 rjjhh = ', rjjhh, ' hours'
107         WRITE(numout,*) '      nb of minutes per hour              rhhmm = ', rhhmm, ' mn'
108         WRITE(numout,*) '      nb of seconds per minute            rmmss = ', rmmss, ' s'
109         WRITE(numout,*)
110         WRITE(numout,*) '      earth radius                         ra   = ', ra   , ' m'
111         WRITE(numout,*) '      gravity                              grav = ', grav , ' m/s^2'
112         WRITE(numout,*)
113         WRITE(numout,*) '      freezing point of water              rt0  = ', rt0  , ' K'
114         WRITE(numout,*)
115         WRITE(numout,*) '   reference density and heat capacity now defined in eosbn2.f90'
116         WRITE(numout,*)
117         WRITE(numout,*) '      thermal conductivity of pure ice          = ', rcnd_i  , ' J/s/m/K'
118         WRITE(numout,*) '      thermal conductivity of snow is defined in a namelist '
119         WRITE(numout,*) '      fresh ice specific heat                   = ', rcpi    , ' J/kg/K'
120         WRITE(numout,*) '      latent heat of fusion of fresh ice / snow = ', rLfus   , ' J/kg'
121         WRITE(numout,*) '      latent heat of subl.  of fresh ice / snow = ', rLsub   , ' J/kg'
122         WRITE(numout,*) '      density of sea ice                        = ', rhoi    , ' kg/m^3'
123         WRITE(numout,*) '      density of snow                           = ', rhos    , ' kg/m^3'
124         WRITE(numout,*) '      density of freshwater (in melt ponds)     = ', rhow    , ' kg/m^3'
125         WRITE(numout,*) '      salinity of ice (for pisces)              = ', sice    , ' psu'
126         WRITE(numout,*) '      salinity of sea (for pisces and isf)      = ', soce    , ' psu'
127         WRITE(numout,*) '      latent heat of evaporation (water)        = ', rLevap  , ' J/m^3' 
128         WRITE(numout,*) '      von Karman constant                       = ', vkarmn 
129         WRITE(numout,*) '      Stefan-Boltzmann constant                 = ', stefan  , ' J/s/m^2/K^4'
130         WRITE(numout,*)
131         WRITE(numout,*) '      conversion: degre ==> radian          rad = ', rad
132         WRITE(numout,*)
133         WRITE(numout,*) '      smallest real computer value       rsmall = ', rsmall
134      ENDIF
135
136   END SUBROUTINE phy_cst
137
138   !!======================================================================
139END MODULE phycst
Note: See TracBrowser for help on using the repository browser.