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

Annotation of /trunk/phylmd/Interface_surf/screenp.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 304 - (hide annotations)
Thu Sep 6 15:51:09 2018 UTC (5 years, 9 months ago) by guez
File size: 3940 byte(s)
Variable fevap of physiq is not used. Remove it from physiq and from
the restart file. Remove the corresponding argument evap of
pbl_surface.

Use directly yqsurf instead of qairsol in pbl_surface.

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

  ViewVC Help
Powered by ViewVC 1.1.21