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

Contents of /trunk/Sources/phylmd/screenp.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: 4124 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 screenp_m
2
3 IMPLICIT none
4
5 contains
6
7 SUBROUTINE screenp(knon, speed, tair, qair, ts, qsurf, rugos, lmon, ustar, &
8 testar, qstar, zref, delu, delte, delq)
9
10 ! From LMDZ4/libf/phylmd/screenp.F90, version 1.1.1.1, 2004/05/19 12:53:09
11
12 ! Objet : calcul "pr\'edicteur" des anomalies du vent, de la
13 ! temp\'erature potentielle et de l'humidit\'e relative au niveau
14 ! de r\'ef\'erence zref et par rapport au 1er niveau (pour u) ou
15 ! \`a la surface (pour theta et q) \`a partir des relations de
16 ! Dyer-Businger.
17
18 ! Reference: Hess, Colman et McAvaney (1995)
19
20 ! I. Musat, 01.07.2002
21
22 use dimphy, only: klon
23
24 INTEGER, intent(in):: knon
25 ! knon----input-I- nombre de points pour un type de surface
26 REAL, dimension(klon), intent(in):: speed, tair, qair
27 ! speed---input-R- module du vent au 1er niveau du modele
28 ! tair----input-R- temperature de l'air au 1er niveau du modele
29 ! qair----input-R- humidite relative au 1er niveau du modele
30 REAL, dimension(klon), intent(in):: ts, qsurf, rugos
31 ! ts------input-R- temperature de l'air a la surface
32 ! qsurf---input-R- humidite relative a la surface
33 ! rugos---input-R- rugosite
34 DOUBLE PRECISION, dimension(klon), intent(in):: lmon
35 ! lmon----input-R- longueur de Monin-Obukov
36 REAL, dimension(klon), intent(in):: ustar, testar, qstar
37 ! ustar---input-R- facteur d'echelle pour le vent
38 ! testar--input-R- facteur d'echelle pour la temperature potentielle
39 ! qstar---input-R- facteur d'echelle pour l'humidite relative
40 REAL, intent(in):: zref
41 ! zref----input-R- altitude de reference
42
43 REAL, dimension(klon), intent(out):: delu
44 ! delu----input-R- anomalie du vent par rapport au 1er niveau
45
46 REAL, dimension(klon), intent(out):: delte
47 ! anomalie de la temperature potentielle par rapport a la surface
48
49 REAL, dimension(klon), intent(out):: delq
50 ! delq----input-R- anomalie de l'humidite relative par rapport a la surface
51
52 ! Local:
53 REAL, PARAMETER:: RKAR=0.40
54 INTEGER i
55 REAL xtmp, xtmp0
56
57 !-------------------------------------------------------------------------
58
59 DO i = 1, knon
60 IF (lmon(i) >= 0.) THEN
61 ! STABLE CASE
62 IF (speed(i) > 1.5.AND.lmon(i) <= 1.0) THEN
63 delu(i) = (ustar(i)/RKAR)* &
64 (log(zref/(rugos(i))+1.) + &
65 min(5d0, 5d0 *(zref - rugos(i))/lmon(i)))
66 delte(i) = (testar(i)/RKAR)* &
67 (log(zref/(rugos(i))+1.) + &
68 min(5d0, 5d0 * (zref - rugos(i))/lmon(i)))
69 delq(i) = (qstar(i)/RKAR)* &
70 (log(zref/(rugos(i))+1.) + &
71 min(5d0, 5d0 * (zref - rugos(i))/lmon(i)))
72 ELSE
73 delu(i) = 0.1 * speed(i)
74 delte(i) = 0.1 * (tair(i) - ts(i))
75 delq(i) = 0.1 * (max(qair(i), 0.0) - max(qsurf(i), 0.0))
76 ENDIF
77 ELSE
78 ! UNSTABLE CASE
79 IF (speed(i) > 5.0.AND.abs(lmon(i)) <= 50.0) THEN
80 xtmp = (1. - 16. * (zref/lmon(i)))**(1./4.)
81 xtmp0 = (1. - 16. * (rugos(i)/lmon(i)))**(1./4.)
82 delu(i) = (ustar(i)/RKAR)* &
83 (log(zref/(rugos(i))+1.) &
84 - 2.*log(0.5*(1. + xtmp)) &
85 + 2.*log(0.5*(1. + xtmp0)) &
86 - log(0.5*(1. + xtmp*xtmp)) &
87 + log(0.5*(1. + xtmp0*xtmp0)) &
88 + 2.*atan(xtmp) - 2.*atan(xtmp0))
89 delte(i) = (testar(i)/RKAR)* &
90 (log(zref/(rugos(i))+1.) &
91 - 2.0 * log(0.5*(1. + xtmp*xtmp)) &
92 + 2.0 * log(0.5*(1. + xtmp0*xtmp0)))
93 delq(i) = (qstar(i)/RKAR)* &
94 (log(zref/(rugos(i))+1.) &
95 - 2.0 * log(0.5*(1. + xtmp*xtmp)) &
96 + 2.0 * log(0.5*(1. + xtmp0*xtmp0)))
97 ELSE
98 delu(i) = 0.5 * speed(i)
99 delte(i) = 0.5 * (tair(i) - ts(i))
100 delq(i) = 0.5 * (max(qair(i), 0.0) - max(qsurf(i), 0.0))
101 ENDIF
102 ENDIF
103 ENDDO
104
105 END SUBROUTINE screenp
106
107 end module screenp_m

  ViewVC Help
Powered by ViewVC 1.1.21