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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 341 - (show annotations)
Mon Oct 21 06:11:44 2019 UTC (4 years, 6 months ago) by guez
File size: 4360 byte(s)
Remove intermediate variables in `pbl_surface`

Remove file `diagcld2.f90`, no longer used since revision 340.

In procedure cdrag, rename zcdn to cdn. In procedure `interfsurf_hq`,
rename `temp_air` to t1lay: this is the corresponding name in
`calcul_fluxs`, is consistent with the other names `[uvq]1lay` and is
more precise.

In procedure `pbl_surface`, rename t and q to `t_seri` and `q_seri`,
which are the names in procedure physiq. Remove needless intermediate
variables qair1, tairsol, psfce, patm and zgeo1. Remove useless
initialization of yrugos. Remove a useless assignment `i = ni(j)`.

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

  ViewVC Help
Powered by ViewVC 1.1.21