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

Contents of /trunk/phylmd/Interface_surf/screenp.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: 3956 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 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 and McAvaney (1995)
19
20 ! I. Musat, July 2002
21
22 use dimphy, only: klon
23
24 INTEGER, intent(in):: knon ! nombre de points pour un type de surface
25 REAL, intent(in):: speed(klon) ! module du vent au 1er niveau du modele
26 REAL, intent(in):: tair(klon) ! temperature de l'air au 1er niveau du modele
27
28 REAL, intent(in):: qair(:) ! (knon)
29 ! humidite relative au 1er niveau du modele
30
31 REAL, intent(in):: ts(:) ! (knon) temperature de l'air a la surface
32 REAL, intent(in):: qsurf(:) ! (knon) humidite relative a la surface
33 REAL, intent(in):: rugos(klon) ! rugosite
34 DOUBLE PRECISION, intent(in):: lmon(klon) ! longueur de Monin-Obukov
35 REAL, intent(in):: ustar(:) ! (knon) facteur d'\'echelle pour le vent
36
37 REAL, intent(in):: testar(klon)
38 ! facteur d'echelle pour la temperature potentielle
39
40 REAL, intent(in):: qstar(klon) ! facteur d'echelle pour l'humidite relative
41 REAL, intent(in):: zref ! altitude de reference
42 REAL, intent(out):: delu(klon) ! anomalie du vent par rapport au 1er niveau
43
44 REAL, intent(out):: delte(klon)
45 ! anomalie de la temperature potentielle par rapport a la surface
46
47 REAL, intent(out):: delq(klon)
48 ! anomalie de l'humidite relative par rapport a la surface
49
50 ! Local:
51 REAL, PARAMETER:: RKAR=0.40
52 INTEGER i
53 REAL xtmp, xtmp0
54
55 !-------------------------------------------------------------------------
56
57 DO i = 1, knon
58 IF (lmon(i) >= 0.) THEN
59 ! STABLE CASE
60 IF (speed(i) > 1.5.AND.lmon(i) <= 1.0) THEN
61 delu(i) = (ustar(i)/RKAR)* &
62 (log(zref/(rugos(i))+1.) + &
63 min(5d0, 5d0 *(zref - rugos(i))/lmon(i)))
64 delte(i) = (testar(i)/RKAR)* &
65 (log(zref/(rugos(i))+1.) + &
66 min(5d0, 5d0 * (zref - rugos(i))/lmon(i)))
67 delq(i) = (qstar(i)/RKAR)* &
68 (log(zref/(rugos(i))+1.) + &
69 min(5d0, 5d0 * (zref - rugos(i))/lmon(i)))
70 ELSE
71 delu(i) = 0.1 * speed(i)
72 delte(i) = 0.1 * (tair(i) - ts(i))
73 delq(i) = 0.1 * (max(qair(i), 0.0) - max(qsurf(i), 0.0))
74 ENDIF
75 ELSE
76 ! UNSTABLE CASE
77 IF (speed(i) > 5.0.AND.abs(lmon(i)) <= 50.0) THEN
78 xtmp = (1. - 16. * (zref/lmon(i)))**(1./4.)
79 xtmp0 = (1. - 16. * (rugos(i)/lmon(i)))**(1./4.)
80 delu(i) = (ustar(i)/RKAR)* &
81 (log(zref/(rugos(i))+1.) &
82 - 2.*log(0.5*(1. + xtmp)) &
83 + 2.*log(0.5*(1. + xtmp0)) &
84 - log(0.5*(1. + xtmp*xtmp)) &
85 + log(0.5*(1. + xtmp0*xtmp0)) &
86 + 2.*atan(xtmp) - 2.*atan(xtmp0))
87 delte(i) = (testar(i)/RKAR)* &
88 (log(zref/(rugos(i))+1.) &
89 - 2.0 * log(0.5*(1. + xtmp*xtmp)) &
90 + 2.0 * log(0.5*(1. + xtmp0*xtmp0)))
91 delq(i) = (qstar(i)/RKAR)* &
92 (log(zref/(rugos(i))+1.) &
93 - 2.0 * log(0.5*(1. + xtmp*xtmp)) &
94 + 2.0 * log(0.5*(1. + xtmp0*xtmp0)))
95 ELSE
96 delu(i) = 0.5 * speed(i)
97 delte(i) = 0.5 * (tair(i) - ts(i))
98 delq(i) = 0.5 * (max(qair(i), 0.0) - max(qsurf(i), 0.0))
99 ENDIF
100 ENDIF
101 ENDDO
102
103 END SUBROUTINE screenp
104
105 end module screenp_m

  ViewVC Help
Powered by ViewVC 1.1.21