/[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 221 - (hide annotations)
Thu Apr 20 14:44:47 2017 UTC (7 years, 1 month ago) by guez
Original Path: trunk/Sources/phylmd/Interface_surf/calcul_fluxs.f
File size: 4226 byte(s)
clcdrag is no longer used in LMDZ. Replaced by cdrag in LMDZ. In cdrag
in LMDZ, zxli is a symbolic constant, false. So removed case zxli true
in LMDZE.

read_sst is called zero (if no ocean point on the whole planet) time or
once per call of physiq. If mod(itap - 1, lmt_pas) == 0 then we have
advanced in time of lmt_pas and deja_lu is necessarily false.

qsat[sl] and dqsat[sl] were never called.

Added output of qsurf in histins, following LMDZ.

Last dummy argument dtime of phystokenc is always the same as first
dummy argument pdtphys, removed dtime.

Removed make rules for nag_xref95, since it does not exist any longer.

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

  ViewVC Help
Powered by ViewVC 1.1.21