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

Contents of /trunk/phylmd/Interface_surf/cdrag.f90

Parent Directory Parent Directory | Revision Log Revision Log


Revision 328 - (show annotations)
Thu Jun 13 14:40:06 2019 UTC (4 years, 11 months ago) by guez
File size: 4255 byte(s)
Change all `.f` suffixes to `.f90`. (The opposite was done in revision
82.)  Because of change of philosopy in GNUmakefile: we already had a
rewritten rule for `.f`, so it does not make the makefile longer to
replace it by a rule for `.f90`. And it spares us options of
makedepf90 and of the compiler. Also we prepare the way for a simpler
`CMakeLists.txt`.

1 module cdrag_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE cdrag(nsrf, speed, t, q, zgeop, psol, ts, qsurf, rugos, cdragm, &
8 cdragh, pref)
9
10 ! From LMDZ4/libf/phylmd/clcdrag.F90 and
11 ! LMDZ4/libf/phylmd/coefcdrag.F90, version 1.1.1.1, 2004/05/19
12 ! 12:53:07
13
14 ! Objet : calcul des drag coefficients au sol pour le moment et
15 ! les flux de chaleurs sensible et latente et calcul de la
16 ! pression au niveau de reference.
17
18 ! Ionela MUSAT, July, 1st, 2002
19
20 ! Louis, J. F., Tiedtke, M. and Geleyn, J. F., 1982. A short
21 ! history of the operational PBL parametrization at
22 ! ECMWF. Workshop on boundary layer parametrization, November
23 ! 1981, ECMWF, Reading, England. Page: 19. Equations in Table 1.
24
25 ! Miller, M. J., A. C. M. Beljaars, T. N. Palmer, 1992. The
26 ! sensitivity of the ECMWF model to the parameterization of
27 ! evaporation from the tropical oceans. J. Climate, 5:418-434.
28
29 use nr_util, only: assert_eq
30
31 use clesphys, only: f_cdrag_oce, f_cdrag_ter
32 use indicesol, only: is_oce
33 use SUPHEC_M, only: rcpd, rd, retv, rg
34 USE yoethf_m, ONLY: rvtmp2
35
36 INTEGER, intent(in):: nsrf ! indice pour le type de surface
37
38 REAL, intent(in):: speed(:) ! (knon)
39 ! norm of the wind at the first model level
40
41 REAL, intent(in):: t(:) ! (knon)
42 ! temperature de l'air au 1er niveau du modele
43
44 REAL, intent(in):: q(:) ! (knon) ! humidite de l'air au 1er niveau du modele
45
46 REAL, intent(in):: zgeop(:) ! (knon)
47 ! g\'eopotentiel au 1er niveau du mod\`ele
48
49 REAL, intent(in) :: psol(:) ! (knon) pression au sol
50 REAL, intent(in):: ts(:) ! (knon) temperature de l'air a la surface
51 REAL, intent(in):: qsurf(:) ! (knon) humidite de l'air a la surface
52 REAL, intent(in):: rugos(:) ! (knon) rugosit\'e
53 REAL, intent(out):: cdragm(:) ! (knon) drag coefficient pour le moment
54
55 REAL, intent(out):: cdragh(:) ! (knon)
56 ! drag coefficient pour les flux de chaleur latente et sensible
57
58 REAL, intent(out), optional:: pref(:) ! (knon) pression au niveau zgeop / RG
59
60 ! Local:
61
62 REAL, PARAMETER:: ckap = 0.4, cb = 5., cc = 5., cd = 5., cepdu2 = 0.1**2
63 real, parameter:: f_ri_cd_min = 0.1
64 INTEGER i, knon
65 REAL zdu2, ztsolv, ztvd, zscf, zucf
66 real zcdn ! drag coefficient neutre
67
68 REAL zri
69 ! nombre de Richardson entre la surface et le niveau de reference
70 ! zgeop / RG
71
72 !-------------------------------------------------------------------------
73
74 knon = assert_eq([size(speed), size(t), size(q), size(zgeop), size(ts), &
75 size(qsurf), size(rugos), size(cdragm), size(cdragh)], "cdrag knon")
76
77 DO i = 1, knon
78 zdu2 = max(cepdu2, speed(i)**2)
79 ztsolv = ts(i) * (1. + RETV * max(qsurf(i), 0.))
80 ztvd = (t(i) + zgeop(i) / RCPD / (1. + RVTMP2 * q(i))) &
81 * (1. + RETV * q(i))
82 zri = zgeop(i) * (ztvd - ztsolv) / (zdu2 * ztvd)
83 zcdn = (ckap / log(1. + zgeop(i) / (RG * rugos(i))))**2
84
85 IF (zri < 0.) THEN
86 ! situation instable
87 zucf = 1. / (1. + 3. * cb * cc * zcdn &
88 * SQRT(ABS(zri) * (1. + zgeop(i) / (RG * rugos(i)))))
89 cdragm(i) = zcdn * max((1. - 2. * cb * zri * zucf), f_ri_cd_min)
90
91 IF (nsrf == is_oce) then
92 ! Cf. Miller et al. (1992).
93 cdragh(i) = f_cdrag_oce * zcdn * (1. + ((0.0016 &
94 / (zcdn * SQRT(zdu2))) * ABS(ztvd - ztsolv)**(1. &
95 / 3.))**1.25)**(1. / 1.25)
96 else
97 cdragh(i) = f_cdrag_ter * zcdn &
98 * max((1. - 3. * cb * zri * zucf), f_ri_cd_min)
99 end IF
100 ELSE
101 ! Situation stable. Pour \'eviter les incoh\'erences dans
102 ! les cas tr\`es stables, on limite zri \`a 20. Cf Hess et
103 ! al. (1995).
104 zri = min(20., zri)
105 zscf = SQRT(1. + cd * ABS(zri))
106 cdragm(i) = zcdn * max(1. / (1. + 2. * CB * zri / zscf), f_ri_cd_min)
107 cdragh(i) = merge(f_cdrag_oce, f_cdrag_ter, nsrf == is_oce) * zcdn &
108 * max(1. / (1. + 3. * CB * zri * zscf), f_ri_cd_min)
109 ENDIF
110 END DO
111
112 if (present(pref)) &
113 pref = exp(log(psol) - zgeop / (RD * t * (1. + RETV * max(q, 0.))))
114
115 END SUBROUTINE cdrag
116
117 end module cdrag_m

  ViewVC Help
Powered by ViewVC 1.1.21