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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 346 - (show annotations)
Mon Dec 9 20:15:29 2019 UTC (4 years, 5 months ago) by guez
File size: 4974 byte(s)
Rename block to `my_block` in procedure `CLOUDS_GNO` because block is
a Fortran keyword.

Remove computation of palpbla in procedure sw. It was not used nor
output. (Not used nor output either in LMDZ.)

In procedure physiq, define `d_[uv]_con` and add them to `[uv]_seri`
only if `conv_Emanuel`. Thus, we do not need to initialize
`d_[uv]_con` to 0, we do not have to save them and we do not add 0 to
`[uv]_seri`.

In procedure physiq, no need to initialize rnebcon to 0, it is defined
by phyetat0 afterwards.

Check that `iflag_cldcon` is between - 2 and 3.

1 module clqh_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE clqh(julien, nisurf, knindex, tsoil, qsol, mu0, rugos, rugoro, &
8 u1lay, v1lay, coef, cdragh, t, q, ts, paprs, pplay, delp, radsol, &
9 albedo, snow, qsurf, rain_fall, snow_fall, fluxlat, pctsrf_new_sic, &
10 agesno, d_t, d_q, d_ts, z0_new, flux_t, flux_q, dflux_s, dflux_l, &
11 fqcalving, ffonte, run_off_lic_0, run_off_lic)
12
13 ! Author: Z. X. Li (LMD/CNRS)
14 ! Date: 1993 Aug. 18th
15 ! Objet : diffusion verticale de "q" et de "h"
16
17 use climb_hq_down_m, only: climb_hq_down
18 use climb_hq_up_m, only: climb_hq_up
19 USE dimphy, ONLY: klev
20 USE interfsurf_hq_m, ONLY: interfsurf_hq
21 USE suphec_m, ONLY: rkappa
22
23 integer, intent(in):: julien ! jour de l'annee en cours
24 integer, intent(in):: nisurf
25 integer, intent(in):: knindex(:) ! (knon)
26
27 REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
28 ! temperature inside the ground, in K, layer 1 nearest to the surface
29
30 REAL, intent(inout):: qsol(:) ! (knon)
31 ! column-density of water in soil, in kg m-2
32
33 real, intent(in):: mu0(:) ! (knon) cosinus de l'angle solaire zenithal
34 real, intent(in):: rugos(:) ! (knon) rugosite
35 REAL, intent(in):: rugoro(:) ! (knon)
36
37 REAL, intent(in):: u1lay(:), v1lay(:) ! (knon)
38 ! vitesse de la 1ere couche (m / s)
39
40 REAL, intent(in):: coef(:, 2:) ! (knon, 2:klev)
41 ! Le coefficient d'echange (m**2 / s) multiplie par le cisaillement
42 ! du vent (dV / dz)
43
44 REAL, intent(in):: cdragh(:) ! (knon) sans unite
45
46 REAL, intent(in):: t(:, :) ! (knon, klev) air temperature, in K
47 REAL, intent(in):: q(:, :) ! (knon, klev) humidit\'e sp\'ecifique
48 REAL, intent(in):: ts(:) ! (knon) temperature du sol (K)
49
50 REAL, intent(in):: paprs(:, :) ! (knon, klev + 1)
51 ! pression \`a l'inter-couche (Pa)
52
53 REAL, intent(in):: pplay(:, :) ! (knon, klev)
54 ! pression au milieu de couche (Pa)
55
56 REAL, intent(in):: delp(:, :) ! (knon, klev)
57 ! epaisseur de couche en pression (Pa)
58
59 REAL, intent(in):: radsol(:) ! (knon)
60 ! surface net downward radiative flux, in W / m2
61
62 REAL, intent(inout):: albedo(:) ! (knon) albedo de la surface
63
64 REAL, intent(inout):: snow(:) ! (knon)
65 ! column-density of mass of snow at the surface, in kg m-2
66
67 REAL, intent(out):: qsurf(:) ! (knon)
68 ! humidite de l'air au dessus de la surface
69
70 real, intent(in):: rain_fall(:) ! (knon)
71 ! liquid water mass flux (kg / m2 / s), positive down
72
73 real, intent(in):: snow_fall(:) ! (knon)
74 ! solid water mass flux (kg / m2 / s), positive down
75
76 real, intent(out):: fluxlat(:) ! (knon) flux de chaleur latente, en W m-2
77 real, intent(in):: pctsrf_new_sic(:) ! (knon)
78 REAL, intent(inout):: agesno(:) ! (knon)
79 REAL, intent(out):: d_t(:, :) ! (knon, klev) variation of air temperature t
80 REAL, intent(out):: d_q(:, :) ! (knon, klev) incrementation de "q"
81 REAL, intent(out):: d_ts(:) ! (knon) variation of surface temperature
82 real, intent(out):: z0_new(:) ! (knon)
83
84 REAL, intent(out):: flux_t(:) ! (knon)
85 ! (diagnostic) flux de chaleur sensible (Cp T) à la surface,
86 ! positif vers le bas, W / m2
87
88 REAL, intent(out):: flux_q(:) ! (knon)
89 ! flux de la vapeur d'eau à la surface, en kg / (m**2 s)
90
91 REAL, intent(out):: dflux_s(:) ! (knon) derivee du flux sensible dF / dTs
92 REAL, intent(out):: dflux_l(:) ! (knon) derivee du flux latent dF / dTs
93
94 REAL, intent(out):: fqcalving(:) ! (knon)
95 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
96 ! hauteur de neige, en kg / m2 / s
97
98 REAL, intent(out):: ffonte(:) ! (knon)
99 ! flux thermique utilis\'e pour fondre la neige
100
101 REAL, intent(inout):: run_off_lic_0(:) ! (knon)
102 ! run-off glacier au pas de temps precedent
103
104 REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total
105
106 ! Local:
107
108 INTEGER k
109 REAL evap(size(knindex)) ! (knon) evaporation au sol
110 REAL, dimension(size(knindex), klev):: cq, dq, ch, dh ! (knon, klev)
111 REAL pkf(size(knindex), klev) ! (knon, klev)
112 real tsurf_new(size(knindex)) ! (knon)
113
114 !----------------------------------------------------------------
115
116 forall (k = 1:klev) pkf(:, k) = (paprs(:, 1) / pplay(:, k))**RKAPPA
117 ! (La pression de r\'ef\'erence est celle au sol.)
118
119 call climb_hq_down(pkf, cq, dq, ch, dh, paprs, pplay, t, coef, delp, q)
120 CALL interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1lay, &
121 v1lay, t(:, 1), q(:, 1), cdragh, ch(:, 1), cq(:, 1), dh(:, 1), &
122 dq(:, 1), rain_fall, snow_fall, rugos, rugoro, snow, qsurf, ts, &
123 pplay(:, 1), paprs(:, 1), radsol, evap, flux_t, fluxlat, dflux_l, &
124 dflux_s, tsurf_new, albedo, z0_new, pctsrf_new_sic, agesno, &
125 fqcalving, ffonte, run_off_lic_0, run_off_lic)
126 flux_q = - evap
127 d_ts = tsurf_new - ts
128 call climb_hq_up(d_t, d_q, cq, dq, ch, dh, flux_t, flux_q, pkf, t, q)
129
130 END SUBROUTINE clqh
131
132 end module clqh_m

  ViewVC Help
Powered by ViewVC 1.1.21