/[lmdze]/trunk/Sources/phylmd/stdlevvar.f
ViewVC logotype

Contents of /trunk/Sources/phylmd/stdlevvar.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 227 - (show annotations)
Thu Nov 2 15:47:03 2017 UTC (6 years, 6 months ago) by guez
File size: 5840 byte(s)
Rename phisinit to phis in restart.nc: clearer, same name as Fortran variable.

In aaam_bud, use rlat and rlon from phyetat0_m instead of having these
module variables associated to actual arguments in physiq.

In clmain, too many wind variables make the procedure hard to
understand. Use yu(:knon, 1) and yv(:knon, 1) instead of u1lay(:knon)
and v1lay(:knon). Note that when yu(:knon, 1) and yv(:knon, 1) are
used as actual arguments, they are probably copied to new arrays since
the elements are not contiguous. Rename yu10m to wind10m because this
is the norm of wind vector, not its zonal component. Rename yustar to
ustar. Rename uzon and vmer to u1 and v1 since these are wind
components at first layer and u1 and v1 are the names of corresponding
dummy arguments in stdlevvar.

In clmain, rename yzlev to zlev.

In clmain, screenc, stdlevvar and coefcdrag, remove the code
corresponding to zxli true (not used in LMDZ either).

Subroutine ustarhb becomes a function. Simplifications using the fact
that zx_alf2 = 0 and zx_alf1 = 1 (discarding the possibility to change
this).

In procedure vdif_kcay, remove unused dummy argument plev. Remove
useless computations of sss and sssq.

In clouds_gno, exp(100.) would overflow in single precision. Set
maximum to exp(80.) instead.

In physiq, use u(:, 1) and v(:, 1) as arguments to phytrac instead of
creating ad hoc variables yu1 and yv1.

In stdlevvar, rename dummy argument u_10m to wind10m, following the
corresponding modification in clmain. Simplifications using the fact
that ok_pred = 0 and ok_corr = 1 (discarding the possibility to change
this).

1 module stdlevvar_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE stdlevvar(klon, knon, nsrf, u1, v1, t1, q1, z1, ts1, qsurf, &
8 rugos, psol, pat1, t_2m, q_2m, t_10m, q_10m, wind10m, ustar)
9
10 ! From LMDZ4/libf/phylmd/stdlevvar.F90, version 1.3, 2005/05/25 13:10:09
11
12 ! Objet : calcul de la température et de l'humidité relative à 2 m
13 ! et du module du vent à 10 m à partir des relations de
14 ! Dyer-Businger et des équations de Louis.
15
16 ! Reference: Hess, Colman and McAvaney (1995)
17
18 ! Author: I. Musat, July 1st, 2002
19
20 use coefcdrag_m, only: coefcdrag
21 USE suphec_m, ONLY: rg, rkappa
22 use screenc_m, only: screenc
23 use screenp_m, only: screenp
24
25 INTEGER, intent(in):: klon
26 ! dimension de la grille physique (= nb_pts_latitude X nb_pts_longitude)
27
28 INTEGER, intent(in):: knon ! nombre de points pour un type de surface
29 INTEGER, intent(in):: nsrf ! indice pour le type de surface
30 REAL, intent(in):: u1(:) ! (knon) vent zonal au 1er niveau du modele
31 REAL, intent(in):: v1(:) ! (knon) vent meridien au 1er niveau du modele
32 REAL, intent(in):: t1(:) ! (knon) temperature de l'air au 1er
33 ! niveau du modele
34 REAL, intent(in):: q1(klon) ! humidite relative au 1er niveau du modele
35 REAL, intent(in):: z1 (klon) ! geopotentiel au 1er niveau du modele
36 REAL, intent(in):: ts1(klon) ! temperature de l'air a la surface
37 REAL, intent(in):: qsurf(klon) ! humidite relative a la surface
38 REAL, intent(in):: rugos(klon) ! rugosite
39 REAL, intent(in):: psol(klon) ! pression au sol
40 REAL, intent(in):: pat1(klon) ! pression au 1er niveau du modele
41 REAL, intent(out):: t_2m(klon) ! temperature de l'air a 2m
42 REAL, intent(out):: q_2m(klon) ! humidite relative a 2m
43 REAL, intent(out):: t_10m(klon) ! temperature de l'air a 10m
44 REAL, intent(out):: q_10m(klon) ! humidite specifique a 10m
45 REAL, intent(out):: wind10m(:) ! (knon) norme du vent \`a 10m
46 REAL, intent(out):: ustar(klon) ! u*
47
48 ! Local:
49 REAL, PARAMETER:: RKAR = 0.4 ! constante de von Karman
50 INTEGER, parameter:: niter = 2 ! nombre iterations calcul "corrector"
51 INTEGER i, n
52 REAL zref
53 REAL, dimension(klon):: speed
54 ! tpot : temperature potentielle
55 REAL, dimension(klon):: tpot
56 REAL, dimension(klon):: zri1, cdran
57 REAL cdram(klon), cdrah(klon)
58 ! ri1 : nb. de Richardson entre la surface --> la 1ere couche
59 REAL, dimension(klon):: ri1
60 REAL, dimension(klon):: testar, qstar
61 REAL, dimension(klon):: zdte, zdq
62 ! lmon : longueur de Monin-Obukhov selon Hess, Colman and McAvaney
63 DOUBLE PRECISION, dimension(klon):: lmon
64 REAL, dimension(klon):: delu, delte, delq
65 REAL, dimension(klon):: u_zref, te_zref, q_zref
66 REAL, dimension(klon):: temp, pref
67
68 !-------------------------------------------------------------------------
69
70 DO i=1, knon
71 speed(i)=SQRT(u1(i)**2+v1(i)**2)
72 ri1(i) = 0.0
73 ENDDO
74
75 CALL coefcdrag(knon, nsrf, speed(:knon), t1(:knon), q1(:knon), &
76 z1(:knon), psol(:knon), ts1, qsurf, rugos, cdram, cdrah, cdran, &
77 zri1, pref)
78
79 ! Star variables
80
81 DO i = 1, knon
82 ri1(i) = zri1(i)
83 tpot(i) = t1(i)* (psol(i)/pat1(i))**RKAPPA
84 ustar(i) = sqrt(cdram(i) * speed(i) * speed(i))
85 zdte(i) = tpot(i) - ts1(i)
86 zdq(i) = max(q1(i), 0.0) - max(qsurf(i), 0.0)
87
88 zdte(i) = sign(max(abs(zdte(i)), 1.e-10), zdte(i))
89
90 testar(i) = (cdrah(i) * zdte(i) * speed(i))/ustar(i)
91 qstar(i) = (cdrah(i) * zdq(i) * speed(i))/ustar(i)
92 lmon(i) = (ustar(i) * ustar(i) * tpot(i)) / (RKAR * RG * testar(i))
93 ENDDO
94
95 ! First aproximation of variables at zref
96 zref = 2.0
97 CALL screenp(knon, speed, tpot, q1, ts1, qsurf, rugos, lmon, ustar, &
98 testar, qstar, zref, delu, delte, delq)
99
100 DO i = 1, knon
101 u_zref(i) = delu(i)
102 q_zref(i) = max(qsurf(i), 0.0) + delq(i)
103 te_zref(i) = ts1(i) + delte(i)
104 temp(i) = te_zref(i) * (psol(i)/pat1(i))**(-RKAPPA)
105 ENDDO
106
107 ! Iteration of the variables at the reference level zref :
108 ! corrector calculation ; see Hess & McAvaney, 1995
109
110 DO n = 1, niter
111 CALL screenc(klon, knon, nsrf, u_zref, temp, q_zref, zref, ts1, &
112 qsurf, rugos, psol, ustar, testar, qstar, pref, delu, delte, delq)
113
114 DO i = 1, knon
115 u_zref(i) = delu(i)
116 q_zref(i) = delq(i) + max(qsurf(i), 0.0)
117 te_zref(i) = delte(i) + ts1(i)
118
119 ! return to normal temperature
120 temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
121 ENDDO
122 ENDDO
123
124 ! verifier le critere de convergence : 0.25% pour te_zref et 5% pour qe_zref
125
126 DO i = 1, knon
127 t_2m(i) = temp(i)
128 q_2m(i) = q_zref(i)
129 ENDDO
130
131 ! First aproximation of variables at zref
132
133 zref = 10.
134 CALL screenp(knon, speed, tpot, q1, ts1, qsurf, rugos, lmon, ustar, &
135 testar, qstar, zref, delu, delte, delq)
136
137 DO i = 1, knon
138 u_zref(i) = delu(i)
139 q_zref(i) = max(qsurf(i), 0.0) + delq(i)
140 te_zref(i) = ts1(i) + delte(i)
141 temp(i) = te_zref(i) * (psol(i)/pat1(i))**(-RKAPPA)
142 ENDDO
143
144 ! Iteration of the variables at the reference level zref:
145 ! corrector ; see Hess & McAvaney, 1995
146
147 DO n = 1, niter
148 CALL screenc(klon, knon, nsrf, u_zref, temp, q_zref, zref, ts1, &
149 qsurf, rugos, psol, ustar, testar, qstar, pref, delu, delte, delq)
150
151 DO i = 1, knon
152 u_zref(i) = delu(i)
153 q_zref(i) = delq(i) + max(qsurf(i), 0.0)
154 te_zref(i) = delte(i) + ts1(i)
155 temp(i) = te_zref(i) * (psol(i)/pref(i))**(-RKAPPA)
156 ENDDO
157 ENDDO
158
159 DO i = 1, knon
160 wind10m(i) = u_zref(i)
161 t_10m(i) = temp(i)
162 q_10m(i) = q_zref(i)
163 ENDDO
164
165 END subroutine stdlevvar
166
167 end module stdlevvar_m

  ViewVC Help
Powered by ViewVC 1.1.21