source: LMDZ6/branches/Ocean_skin/libf/phylmd/suphel.F90 @ 3601

Last change on this file since 3601 was 3429, checked in by lguez, 5 years ago

Create subdirectory Ocean_skin in libf. For now, Ocean_skin is under
control of git, not subversion.

Add variable eps_w to common YOMCST.

For now, continue to read ocean skin parameters from a namelist in
config_ocean_skin.

The parameterisation is called from procedure surf_ocean.

Add two prognostic variables for the parameterisation: dt_ns and
ds_ns. Add eight diagnostic variables: t_int, s_int, dter, dser, tkt,
tks, rf, taur. The ten variables are only defined on ocean surface,
elsewhere they are set to nf90_fill_real. In pbl_surface, we can
initialize the eight diagnostic variables to nf90_fill_real before the
loop on sub-surfaces, but we need to keep the old values of dt_ns and
ds_ns as input of the parameterisation so we set dt_ns and ds_ns to
nf90_fill_real after the call to surf_ocean. Define ten corresponding
compressed variables in pbl_surface. Define ten corresponding NetCDF
output variables in phys_output_ctrlout_mod.

In procedure pbl_surface_newfrac, for an appearing ocean sub-surface,
dt_ns and ds_ns are set to 0. In phyetat0, also set initial dt_ns and
ds_ns to 0 if they are not in start file.

In procedure surf_ocean, for now, we use a constant specific latent
heat of vaporization, as elsewhere in LMDZ, and a constant bulk
salinity.

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.2 KB
Line 
1
2! $Header$
3
4SUBROUTINE suphel
5
6  IMPLICIT NONE
7
8  include "YOMCST.h"
9  include "YOETHF.h"
10  ! IM cf. JLD
11  LOGICAL firstcall
12  SAVE firstcall
13  !$OMP THREADPRIVATE(firstcall)
14  DATA firstcall/.TRUE./
15
16  IF (firstcall) THEN
17    PRINT *, 'suphel initialise les constantes du GCM'
18    firstcall = .FALSE.
19  ELSE
20    PRINT *, 'suphel DEJA APPELE '
21    RETURN
22  END IF
23  ! -----------------------------------------------------------------
24
25  ! *       1.    DEFINE FUNDAMENTAL CONSTANTS.
26  ! -----------------------------
27
28  WRITE (UNIT=6, FMT='(''0*** Constants of the ICM   ***'')')
29  rpi = 2.*asin(1.)
30  rclum = 299792458.
31  rhpla = 6.6260755E-34
32  rkbol = 1.380658E-23
33  rnavo = 6.0221367E+23
34  WRITE (UNIT=6, FMT='('' *** Fundamental constants ***'')')
35  WRITE (UNIT=6, FMT='(''           PI = '',E13.7,'' -'')') rpi
36  WRITE (UNIT=6, FMT='(''            c = '',E13.7,''m s-1'')') rclum
37  WRITE (UNIT=6, FMT='(''            h = '',E13.7,''J s'')') rhpla
38  WRITE (UNIT=6, FMT='(''            K = '',E13.7,''J K-1'')') rkbol
39  WRITE (UNIT=6, FMT='(''            N = '',E13.7,''mol-1'')') rnavo
40
41  ! ----------------------------------------------------------------
42
43  ! *       2.    DEFINE ASTRONOMICAL CONSTANTS.
44  ! ------------------------------
45
46  rday = 86400.
47  rea = 149597870000.
48  repsm = 0.409093
49
50  rsiyea = 365.25*rday*2.*rpi/6.283076
51  rsiday = rday/(1.+rday/rsiyea)
52  romega = 2.*rpi/rsiday
53
54  ! exp1      R_ecc = 0.05
55  ! exp1      R_peri = 102.04
56  ! exp1      R_incl = 22.5
57  ! exp1      print*, 'Parametres orbitaux modifies'
58  ! ref      R_ecc = 0.016724
59  ! ref      R_peri = 102.04
60  ! ref      R_incl = 23.5
61
62  ! IM 161002 : pour avoir les ctes AMIP II
63  ! IM 161002   R_ecc = 0.016724
64  ! IM 161002   R_peri = 102.04
65  ! IM 161002   R_incl = 23.5
66  ! IM on mets R_ecc, R_peri, R_incl dans conf_phys.F90
67  ! R_ecc = 0.016715
68  ! R_peri = 102.7
69  ! R_incl = 23.441
70
71  WRITE (UNIT=6, FMT='('' *** Astronomical constants ***'')')
72  WRITE (UNIT=6, FMT='(''          day = '',E13.7,'' s'')') rday
73  WRITE (UNIT=6, FMT='('' half g. axis = '',E13.7,'' m'')') rea
74  WRITE (UNIT=6, FMT='('' mean anomaly = '',E13.7,'' -'')') repsm
75  WRITE (UNIT=6, FMT='('' sideral year = '',E13.7,'' s'')') rsiyea
76  WRITE (UNIT=6, FMT='(''  sideral day = '',E13.7,'' s'')') rsiday
77  WRITE (UNIT=6, FMT='(''        omega = '',E13.7,'' s-1'')') romega
78  ! write(unit=6,fmt='('' excentricite = '',e13.7,''-'')')R_ecc
79  ! write(unit=6,fmt='(''     equinoxe = '',e13.7,''-'')')R_peri
80  ! write(unit=6,fmt='(''  inclinaison = '',e13.7,''-'')')R_incl
81
82  ! ------------------------------------------------------------------
83
84  ! *       3.    DEFINE GEOIDE.
85  ! --------------
86
87  rg = 9.80665
88  ra = 6371229.
89  r1sa = sngl(1.D0/dble(ra))
90  WRITE (UNIT=6, FMT='('' ***         Geoide         ***'')')
91  WRITE (UNIT=6, FMT='(''      Gravity = '',E13.7,'' m s-2'')') rg
92  WRITE (UNIT=6, FMT='('' Earth radius = '',E13.7,'' m'')') ra
93  WRITE (UNIT=6, FMT='('' Inverse E.R. = '',E13.7,'' m'')') r1sa
94
95  ! -----------------------------------------------------------------
96
97  ! *       4.    DEFINE RADIATION CONSTANTS.
98  ! ---------------------------
99
100  ! z.x.li      RSIGMA=2. * RPI**5 * RKBOL**4 /(15.* RCLUM**2 * RHPLA**3)
101  rsigma = 2.*rpi**5*(rkbol/rhpla)**3*rkbol/rclum/rclum/15.
102  ! IM init. dans conf_phys.F90   RI0=1365.
103  WRITE (UNIT=6, FMT='('' ***        Radiation       ***'')')
104  WRITE (UNIT=6, FMT='('' Stefan-Bol.  = '',E13.7,'' W m-2 K-4'' &
105    &                                                         &
106    &         )') rsigma
107  ! IM init. dans conf_phys.F90   WRITE(UNIT=6,FMT='('' Solar const. =
108  ! '',E13.7,'' W m-2'')')
109  ! IM init. dans conf_phys.F90  S      RI0
110
111  ! -----------------------------------------------------------------
112
113  ! *       5.    DEFINE THERMODYNAMIC CONSTANTS, GAS PHASE.
114  ! ------------------------------------------
115
116  r = rnavo*rkbol
117  rmd = 28.9644
118  rmo3 = 47.9942
119  rmco2 = 44.011
120  rmc   = 12.0107
121  rmv = 18.0153
122  rd = 1000.*r/rmd
123  rv = 1000.*r/rmv
124  rcpd = 3.5*rd
125  rcvd = rcpd - rd
126  rcpv = 4.*rv
127  rcvv = rcpv - rv
128  rkappa = rd/rcpd
129  eps_w = rmv / rmd
130  retv = rv/rd - 1.
131  WRITE (UNIT=6, FMT='('' *** Thermodynamic, gas     ***'')')
132  WRITE (UNIT=6, FMT='('' Perfect gas  = '',e13.7)') r
133  WRITE (UNIT=6, FMT='('' Dry air mass = '',e13.7)') rmd
134  WRITE (UNIT=6, FMT='('' Ozone   mass = '',e13.7)') rmo3
135  WRITE (UNIT=6, FMT='('' CO2     mass = '',e13.7)') rmco2
136  WRITE (UNIT=6, FMT='('' CO2     mass = '',e13.7)') rmc
137  WRITE (UNIT=6, FMT='('' Vapour  mass = '',e13.7)') rmv
138  WRITE (UNIT=6, FMT='('' Dry air cst. = '',e13.7)') rd
139  WRITE (UNIT=6, FMT='('' Vapour  cst. = '',e13.7)') rv
140  WRITE (UNIT=6, FMT='(''         Cpd  = '',e13.7)') rcpd
141  WRITE (UNIT=6, FMT='(''         Cvd  = '',e13.7)') rcvd
142  WRITE (UNIT=6, FMT='(''         Cpv  = '',e13.7)') rcpv
143  WRITE (UNIT=6, FMT='(''         Cvv  = '',e13.7)') rcvv
144  WRITE (UNIT=6, FMT='(''      Rd/Cpd  = '',e13.7)') rkappa
145  WRITE (UNIT=6, FMT='(''     Rv/Rd-1  = '',e13.7)') retv
146
147  ! ----------------------------------------------------------------
148
149  ! *       6.    DEFINE THERMODYNAMIC CONSTANTS, LIQUID PHASE.
150  ! ---------------------------------------------
151
152  rcw = rcpv
153  WRITE (UNIT=6, FMT='('' *** Thermodynamic, liquid  ***'')')
154  WRITE (UNIT=6, FMT='(''         Cw   = '',E13.7)') rcw
155
156  ! ----------------------------------------------------------------
157
158  ! *       7.    DEFINE THERMODYNAMIC CONSTANTS, SOLID PHASE.
159  ! --------------------------------------------
160
161  rcs = rcpv
162  WRITE (UNIT=6, FMT='('' *** thermodynamic, solid   ***'')')
163  WRITE (UNIT=6, FMT='(''         Cs   = '',E13.7)') rcs
164
165  ! ----------------------------------------------------------------
166
167  ! *       8.    DEFINE THERMODYNAMIC CONSTANTS, TRANSITION OF PHASE.
168  ! ----------------------------------------------------
169
170  rtt = 273.16
171  rlvtt = 2.5008E+6
172  rlstt = 2.8345E+6
173  rlmlt = rlstt - rlvtt
174  ratm = 100000.
175  WRITE (UNIT=6, FMT='('' *** Thermodynamic, trans.  ***'')')
176  WRITE (UNIT=6, FMT='('' Fusion point  = '',E13.7)') rtt
177  WRITE (UNIT=6, FMT='(''        RLvTt  = '',E13.7)') rlvtt
178  WRITE (UNIT=6, FMT='(''        RLsTt  = '',E13.7)') rlstt
179  WRITE (UNIT=6, FMT='(''        RLMlt  = '',E13.7)') rlmlt
180  WRITE (UNIT=6, FMT='('' Normal press. = '',E13.7)') ratm
181  WRITE (UNIT=6, FMT='('' Latent heat :  '')')
182
183  ! ----------------------------------------------------------------
184
185  ! *       9.    SATURATED VAPOUR PRESSURE.
186  ! --------------------------
187
188  restt = 611.14
189  rgamw = (rcw-rcpv)/rv
190  rbetw = rlvtt/rv + rgamw*rtt
191  ralpw = log(restt) + rbetw/rtt + rgamw*log(rtt)
192  rgams = (rcs-rcpv)/rv
193  rbets = rlstt/rv + rgams*rtt
194  ralps = log(restt) + rbets/rtt + rgams*log(rtt)
195  rgamd = rgams - rgamw
196  rbetd = rbets - rbetw
197  ralpd = ralps - ralpw
198
199  ! ------------------------------------------------------------------
200
201  ! *       10.   CONSTANTS FOR THERMODYNAMICAL FUNCTIONS.
202  ! ----------------------------------------
203
204  rvtmp2 = rcpv/rcpd - 1.
205  rhoh2o = ratm/100.
206  r2es = restt*rd/rv
207  r3les = 17.269
208  r3ies = 21.875
209  r4les = 35.86
210  r4ies = 7.66
211  r5les = r3les*(rtt-r4les)
212  r5ies = r3ies*(rtt-r4ies)
213
214  ! ------------------------------------------------------------------
215
216  ! *       10.   CONSTANTS FOR METHANE OXIDATION AND PHOTOLYSIS.
217  ! -----------------------------------------------
218
219  CALL SUMETHOX()
220
221  RETURN
222END SUBROUTINE suphel
Note: See TracBrowser for help on using the repository browser.