/[lmdze]/trunk/libf/phylmd/clcdrag.f90
ViewVC logotype

Contents of /trunk/libf/phylmd/clcdrag.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 62 - (show annotations)
Thu Jul 26 14:37:37 2012 UTC (11 years, 9 months ago) by guez
File size: 4255 byte(s)
Changed handling of compiler in compilation system.

Removed the prefix letters "y", "p", "t" or "z" in some names of variables.

Replaced calls to NetCDF by calls to NetCDF95.

Extracted "ioget_calendar" procedures from "calendar.f90" into a
separate file.

Extracted to a separate file, "mathop2.f90", procedures that were not
part of the generic interface "mathop" in "mathop.f90".

Removed computation of "dq" in "bilan_dyn", which was not used.

In "iniadvtrac", removed schemes 20 Slopes and 30 Prather. Was not
compatible with declarations of array sizes.

In "clcdrag", "ustarhb", "vdif_kcay", "yamada4" and "coefkz", changed
the size of some arrays from "klon" to "knon".

Removed possible call to "conema3" in "physiq".

Removed unused argument "cd" in "yamada".

1 module clcdrag_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE clcdrag(klon, knon, nsrf, zxli, u, v, t, q, zgeop, ts, qsurf, &
8 rugos, pcfm, pcfh)
9
10 ! From LMDZ4/libf/phylmd/clcdrag.F90, version 1.1.1.1 2004/05/19 12:53:07
11
12 USE indicesol, ONLY : is_oce
13 USE suphec_m, ONLY : rcpd, retv, rg
14 USE yoethf_m, ONLY : rvtmp2
15
16 ! Objet : calcul des cdrags pour le moment (pcfm) et les flux de
17 ! chaleur sensible et latente (pcfh).
18
19 ! knon----input-I- nombre de points pour un type de surface
20 ! nsrf----input-I- indice pour le type de surface; voir indicesol.inc
21 ! zxli----input-L- calcul des cdrags selon Laurent Li
22 ! u-------input-R- vent zonal au 1er niveau du modele
23 ! v-------input-R- vent meridien au 1er niveau du modele
24 ! t-------input-R- temperature de l'air au 1er niveau du modele
25 ! q-------input-R- humidite de l'air au 1er niveau du modele
26 ! ts------input-R- temperature de l'air a la surface
27 ! qsurf---input-R- humidite de l'air a la surface
28 ! rugos---input-R- rugosite
29
30 ! pcfm---output-R- cdrag pour le moment
31 ! pcfh---output-R- cdrag pour les flux de chaleur latente et sensible
32
33 INTEGER, intent(in) :: klon
34 ! dimension de la grille physique (= nb_pts_latitude X nb_pts_longitude)
35
36 INTEGER, intent(in) :: knon, nsrf
37
38 ! Fonctions thermodynamiques et fonctions d'instabilite
39 LOGICAL, intent(in) :: zxli ! utiliser un jeu de fonctions simples
40
41 REAL, intent(in), dimension(klon) :: u, v, t, q
42 REAL, intent(in):: zgeop(klon) ! géopotentiel au 1er niveau du modèle
43 REAL, intent(in), dimension(klon) :: ts, qsurf
44 REAL, intent(in), dimension(klon) :: rugos
45 REAL, intent(out):: pcfm(:), pcfh(:) ! (knon)
46
47 ! Quelques constantes et options:
48 REAL, PARAMETER :: ckap=0.40, cb=5.0, cc=5.0, cd=5.0, cepdu2=(0.1)**2
49
50 ! Variables locales :
51 INTEGER :: i
52 REAL :: zdu2, ztsolv, ztvd, zscf
53 REAL :: zucf, zcr
54 REAL :: friv, frih
55 REAL, dimension(klon) :: zcfm1, zcfm2
56 REAL, dimension(klon) :: zcfh1, zcfh2
57 REAL, dimension(klon) :: zcdn
58 REAL, dimension(klon) :: zri
59
60 !--------------------------------------------------------------------
61
62 ! Calculer le frottement au sol (Cdrag)
63
64 DO i = 1, knon
65 zdu2 = max(cepdu2,u(i)**2+v(i)**2)
66 ztsolv = ts(i) * (1.0+RETV*qsurf(i))
67 ztvd = (t(i)+zgeop(i)/RCPD/(1.+RVTMP2*q(i))) &
68 *(1.+RETV*q(i))
69 zri(i) = zgeop(i)*(ztvd-ztsolv)/(zdu2*ztvd)
70 zcdn(i) = (ckap/log(1.+zgeop(i)/(RG*rugos(i))))**2
71
72 IF (zri(i) .gt. 0.) THEN
73 ! situation stable
74 zri(i) = min(20.,zri(i))
75 IF (.NOT. zxli) THEN
76 zscf = SQRT(1.+cd*ABS(zri(i)))
77 FRIV = AMAX1(1. / (1.+2.*CB*zri(i)/ZSCF), 0.1)
78 zcfm1(i) = zcdn(i) * FRIV
79 FRIH = AMAX1(1./ (1.+3.*CB*zri(i)*ZSCF), 0.1 )
80 zcfh1(i) = 0.8 * zcdn(i) * FRIH
81 pcfm(i) = zcfm1(i)
82 pcfh(i) = zcfh1(i)
83 ELSE
84 pcfm(i) = zcdn(i)* fsta(zri(i))
85 pcfh(i) = zcdn(i)* fsta(zri(i))
86 ENDIF
87 ELSE
88 ! situation instable
89 IF (.NOT. zxli) THEN
90 zucf = 1./(1.+3.0*cb*cc*zcdn(i)*SQRT(ABS(zri(i)) &
91 *(1.0+zgeop(i)/(RG*rugos(i)))))
92 zcfm2(i) = zcdn(i)*amax1((1.-2.0*cb*zri(i)*zucf),0.1)
93 zcfh2(i) = 0.8 * zcdn(i)*amax1((1.-3.0*cb*zri(i)*zucf),0.1)
94 pcfm(i) = zcfm2(i)
95 pcfh(i) = zcfh2(i)
96 ELSE
97 pcfm(i) = zcdn(i)* fins(zri(i))
98 pcfh(i) = zcdn(i)* fins(zri(i))
99 ENDIF
100 zcr = (0.0016/(zcdn(i)*SQRT(zdu2)))*ABS(ztvd-ztsolv)**(1./3.)
101 IF(nsrf == is_oce) pcfh(i) = 0.8 * zcdn(i) &
102 * (1. + zcr**1.25)**(1. / 1.25)
103 ENDIF
104 END DO
105
106 contains
107
108 ! Fonctions thermodynamiques et fonctions d'instabilite
109
110 function fsta(x)
111 REAL fsta
112 real, intent(in):: x
113 fsta = 1.0 / (1.0+10.0*x*(1+8.0*x))
114 end function fsta
115
116 !*******************************************************
117
118 function fins(x)
119 REAL fins
120 real, intent(in):: x
121 fins = SQRT(1.0-18.0*x)
122 end function fins
123
124 END SUBROUTINE clcdrag
125
126 end module clcdrag_m

  ViewVC Help
Powered by ViewVC 1.1.21