/[lmdze]/trunk/phylmd/Interface_surf/calcul_fluxs.f
ViewVC logotype

Contents of /trunk/phylmd/Interface_surf/calcul_fluxs.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 266 - (show annotations)
Thu Apr 19 17:54:55 2018 UTC (5 years, 11 months ago) by guez
File size: 4224 byte(s)
Define macros of the preprocessor CPP_IIM, CPP_JJM, CPP_LLM so we can
control the resolution from the compilation command, and automate
compilation for several resolutions.

In module yoethf_m, transform variables into named constants. So we do
not need procedure yoethf any longer.

Bug fix in program test_inter_barxy, missing calls to fyhyp and fxhyp,
and definition of rlatu.

Remove variable iecri of module conf_gcm_m. The files dyn_hist*.nc are
written every time step. We are simplifying the output system, pending
replacement by a whole new system.

Modify possible value of vert_sampling from "param" to
"strato_custom", following LMDZ. Default values of corresponding
namelist variables are now the values used for LMDZ CMIP6.

1 module calcul_fluxs_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE calcul_fluxs(dtime, tsurf, p1lay, cal, beta, coef1lay, ps, &
8 qsurf, radsol, dif_grnd, t1lay, q1lay, u1lay, v1lay, petAcoef, &
9 peqAcoef, petBcoef, peqBcoef, tsurf_new, evap, fluxlat, flux_t, &
10 dflux_s, dflux_l)
11
12 ! Cette routine calcule les flux en h et q à l'interface et une
13 ! température de surface.
14
15 ! L. Fairhead, April 2000
16
17 USE fcttre, ONLY: foede, foeew
18 use nr_util, only: assert_eq
19 USE suphec_m, ONLY: rcpd, rd, retv, rlstt, rlvtt, rtt
20 USE yoethf_m, ONLY: r2es, r5ies, r5les, rvtmp2
21
22 real, intent(IN):: dtime
23 real, intent(IN):: tsurf(:) ! (knon) température de surface
24
25 real, intent(IN):: p1lay(:) ! (knon)
26 ! pression première couche (milieu de couche)
27
28 real, intent(IN):: cal(:) ! (knon) capacité calorifique du sol
29 real, intent(IN):: beta(:) ! (knon) évaporation réelle
30 real, intent(IN):: coef1lay(:) ! (knon) coefficient d'échange
31 real, intent(IN):: ps(:) ! (knon) pression au sol
32 real, intent(OUT):: qsurf(:) ! (knon) humidité de l'air au-dessus du sol
33
34 real, intent(IN):: radsol(:) ! (knon)
35 ! rayonnement net au sol (longwave + shortwave)
36
37 real, intent(IN):: dif_grnd(:) ! (knon)
38 ! coefficient de diffusion vers le sol profond
39
40 real, intent(IN):: t1lay(:), q1lay(:), u1lay(:), v1lay(:) ! (knon)
41
42 real, intent(IN):: petAcoef(:), peqAcoef(:) ! (knon)
43 ! coefficients A de la résolution de la couche limite pour T et q
44
45 real, intent(IN):: petBcoef(:), peqBcoef(:) ! (knon)
46 ! coefficients B de la résolution de la couche limite pour t et q
47
48 real, intent(OUT):: tsurf_new(:) ! (knon) température au sol
49 real, intent(OUT):: evap(:) ! (knon)
50
51 real, intent(OUT):: fluxlat(:), flux_t(:) ! (knon)
52 ! flux de chaleurs latente et sensible
53
54 real, intent(OUT):: dflux_s(:), dflux_l(:) ! (knon)
55 ! dérivées des flux de chaleurs sensible et latente par rapport à
56 ! Ts (W m-2 K-1)
57
58 ! Local:
59 integer i
60 integer knon ! nombre de points a traiter
61 real, dimension(size(ps)):: mh, oh, mq, nq, oq, dq_s_dt, coef ! (knon)
62 real qsat(size(ps)) ! (knon) mass fraction
63 real sl(size(ps)) ! (knon) chaleur latente d'évaporation ou de sublimation
64 logical delta
65 real zcor
66 real, parameter:: t_grnd = 271.35
67
68 !---------------------------------------------------------------------
69
70 knon = assert_eq((/size(tsurf), size(p1lay), size(cal), size(beta), &
71 size(coef1lay), size(ps), size(qsurf), size(radsol), size(dif_grnd), &
72 size(t1lay), size(q1lay), size(u1lay), size(v1lay), size(petAcoef), &
73 size(peqAcoef), size(petBcoef), size(peqBcoef), size(tsurf_new), &
74 size(evap), size(fluxlat), size(flux_t), size(dflux_s), &
75 size(dflux_l)/), "calcul_fluxs knon")
76
77 ! Traitement de l'humidité du sol
78
79 DO i = 1, knon
80 delta = rtt >= tsurf(i)
81 qsat(i) = MIN(0.5, r2es * FOEEW(tsurf(i), delta) / ps(i))
82 zcor = 1. / (1. - retv * qsat(i))
83 qsat(i) = qsat(i) * zcor
84 dq_s_dt(i) = RCPD * FOEDE(tsurf(i), delta, merge(R5IES * RLSTT, &
85 R5LES * RLVTT, delta) / RCPD / (1. + RVTMP2 * q1lay(i)), &
86 qsat(i), zcor) / RLVTT
87 ENDDO
88
89 coef = coef1lay * (1. + SQRT(u1lay**2 + v1lay**2)) * p1lay / (RD * t1lay)
90 sl = merge(RLSTT, RLVTT, tsurf < RTT)
91
92 ! Q
93 oq = 1. - beta * coef * peqBcoef * dtime
94 mq = beta * coef * (peqAcoef - qsat + dq_s_dt * tsurf) / oq
95 nq = beta * coef * (- 1. * dq_s_dt) / oq
96
97 ! H
98 oh = 1. - (coef * petBcoef * dtime)
99 mh = coef * petAcoef / oh
100 dflux_s = - (coef * RCPD)/ oh
101
102 ! Tsurface
103 tsurf_new = (tsurf + cal / RCPD * dtime * (radsol + mh + sl * mq) &
104 + dif_grnd * t_grnd * dtime) / (1. - dtime * cal / RCPD * (dflux_s &
105 + sl * nq) + dtime * dif_grnd)
106
107 evap = - mq - nq * tsurf_new
108 fluxlat = - evap * sl
109 flux_t = mh + dflux_s * tsurf_new
110 dflux_l = sl * nq
111
112 ! Nouvelle valeur de l'humidité au dessus du sol :
113 qsurf = (peqAcoef - peqBcoef * evap * dtime) * (1. - beta) + beta * (qsat &
114 + dq_s_dt * (tsurf_new - tsurf))
115
116 END SUBROUTINE calcul_fluxs
117
118 end module calcul_fluxs_m

  ViewVC Help
Powered by ViewVC 1.1.21