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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 311 - (hide annotations)
Mon Dec 3 17:52:21 2018 UTC (5 years, 6 months ago) by guez
File size: 4292 byte(s)
Move file cv_thermo.f to directory CV30_routines since it is only used
there. Rename module cv_thermo_m to cv_thermo.

Named constants instead of variables in module suphec_m.

Rename dummy argument spechum of procedure interfsurf_hq to q1lay
(same as corresponding dummy argument in calcul_fluxs).

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

  ViewVC Help
Powered by ViewVC 1.1.21