/[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 341 - (show annotations)
Mon Oct 21 06:11:44 2019 UTC (4 years, 7 months ago) by guez
File size: 4899 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 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 REAL, intent(inout):: tsoil(:, :) ! (knon, nsoilmx)
27
28 REAL, intent(inout):: qsol(:) ! (knon)
29 ! column-density of water in soil, in kg m-2
30
31 real, intent(in):: mu0(:) ! (knon) cosinus de l'angle solaire zenithal
32 real, intent(in):: rugos(:) ! (knon) rugosite
33 REAL, intent(in):: rugoro(:) ! (knon)
34
35 REAL, intent(in):: u1lay(:), v1lay(:) ! (knon)
36 ! vitesse de la 1ere couche (m / s)
37
38 REAL, intent(in):: coef(:, 2:) ! (knon, 2:klev)
39 ! Le coefficient d'echange (m**2 / s) multiplie par le cisaillement
40 ! du vent (dV / dz)
41
42 REAL, intent(in):: cdragh(:) ! (knon) sans unite
43
44 REAL, intent(in):: t(:, :) ! (knon, klev) air temperature, in K
45 REAL, intent(in):: q(:, :) ! (knon, klev) humidit\'e sp\'ecifique
46 REAL, intent(in):: ts(:) ! (knon) temperature du sol (K)
47
48 REAL, intent(in):: paprs(:, :) ! (knon, klev + 1)
49 ! pression \`a l'inter-couche (Pa)
50
51 REAL, intent(in):: pplay(:, :) ! (knon, klev)
52 ! pression au milieu de couche (Pa)
53
54 REAL, intent(in):: delp(:, :) ! (knon, klev)
55 ! epaisseur de couche en pression (Pa)
56
57 REAL, intent(in):: radsol(:) ! (knon)
58 ! surface net downward radiative flux, in W / m2
59
60 REAL, intent(inout):: albedo(:) ! (knon) albedo de la surface
61
62 REAL, intent(inout):: snow(:) ! (knon)
63 ! column-density of mass of snow at the surface, in kg m-2
64
65 REAL, intent(out):: qsurf(:) ! (knon)
66 ! humidite de l'air au dessus de la surface
67
68 real, intent(in):: rain_fall(:) ! (knon)
69 ! liquid water mass flux (kg / m2 / s), positive down
70
71 real, intent(in):: snow_fall(:) ! (knon)
72 ! solid water mass flux (kg / m2 / s), positive down
73
74 real, intent(out):: fluxlat(:) ! (knon) flux de chaleur latente, en W m-2
75 real, intent(in):: pctsrf_new_sic(:) ! (knon)
76 REAL, intent(inout):: agesno(:) ! (knon)
77 REAL, intent(out):: d_t(:, :) ! (knon, klev) variation of air temperature t
78 REAL, intent(out):: d_q(:, :) ! (knon, klev) incrementation de "q"
79 REAL, intent(out):: d_ts(:) ! (knon) variation of surface temperature
80 real, intent(out):: z0_new(:) ! (knon)
81
82 REAL, intent(out):: flux_t(:) ! (knon)
83 ! (diagnostic) flux de chaleur sensible (Cp T) à la surface,
84 ! positif vers le bas, W / m2
85
86 REAL, intent(out):: flux_q(:) ! (knon)
87 ! flux de la vapeur d'eau à la surface, en kg / (m**2 s)
88
89 REAL, intent(out):: dflux_s(:) ! (knon) derivee du flux sensible dF / dTs
90 REAL, intent(out):: dflux_l(:) ! (knon) derivee du flux latent dF / dTs
91
92 REAL, intent(out):: fqcalving(:) ! (knon)
93 ! Flux d'eau "perdue" par la surface et n\'ecessaire pour que limiter la
94 ! hauteur de neige, en kg / m2 / s
95
96 REAL, intent(out):: ffonte(:) ! (knon)
97 ! flux thermique utilis\'e pour fondre la neige
98
99 REAL, intent(inout):: run_off_lic_0(:) ! (knon)
100 ! run-off glacier au pas de temps precedent
101
102 REAL, intent(OUT):: run_off_lic(:) ! (knon) ruissellement total
103
104 ! Local:
105
106 INTEGER k
107 REAL evap(size(knindex)) ! (knon) evaporation au sol
108 REAL, dimension(size(knindex), klev):: cq, dq, ch, dh ! (knon, klev)
109 REAL pkf(size(knindex), klev) ! (knon, klev)
110 real tsurf_new(size(knindex)) ! (knon)
111
112 !----------------------------------------------------------------
113
114 forall (k = 1:klev) pkf(:, k) = (paprs(:, 1) / pplay(:, k))**RKAPPA
115 ! (La pression de r\'ef\'erence est celle au sol.)
116
117 call climb_hq_down(pkf, cq, dq, ch, dh, paprs, pplay, t, coef, delp, q)
118 CALL interfsurf_hq(julien, mu0, nisurf, knindex, tsoil, qsol, u1lay, &
119 v1lay, t(:, 1), q(:, 1), cdragh, ch(:, 1), cq(:, 1), dh(:, 1), &
120 dq(:, 1), rain_fall, snow_fall, rugos, rugoro, snow, qsurf, ts, &
121 pplay(:, 1), paprs(:, 1), radsol, evap, flux_t, fluxlat, dflux_l, &
122 dflux_s, tsurf_new, albedo, z0_new, pctsrf_new_sic, agesno, &
123 fqcalving, ffonte, run_off_lic_0, run_off_lic)
124 flux_q = - evap
125 d_ts = tsurf_new - ts
126 call climb_hq_up(d_t, d_q, cq, dq, ch, dh, flux_t, flux_q, pkf, t, q)
127
128 END SUBROUTINE clqh
129
130 end module clqh_m

  ViewVC Help
Powered by ViewVC 1.1.21