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

Annotation of /trunk/Sources/phylmd/coefcdrag.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 227 - (hide annotations)
Thu Nov 2 15:47:03 2017 UTC (6 years, 7 months ago) by guez
File size: 4119 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 guez 108 module coefcdrag_m
2    
3     IMPLICIT none
4    
5     contains
6    
7 guez 227 SUBROUTINE coefcdrag (knon, nsrf, speed, t, q, zgeop, psol, ts, qsurf, &
8     rugos, cdram, cdrah, cdran, zri1, pref)
9 guez 108
10 guez 227 ! From LMDZ4/libf/phylmd/coefcdrag.F90, version 1.1.1.1, 2004/05/19 12:53:07
11 guez 108
12 guez 227 ! Objet : calcul des cdrags pour le moment (cdram) et les flux de
13     ! chaleur sensible et latente (cdrah), du cdrag neutre (cdran), du
14     ! nombre de Richardson entre la surface et le niveau de reference
15     ! (zri1) et de la pression au niveau de reference (pref).
16    
17 guez 108 ! I. Musat, 01.07.2002
18 guez 227
19     use indicesol, only: is_oce
20     use SUPHEC_M, only: rd, retv, rg, rkappa
21     use dimphy, only: klon
22    
23     INTEGER, intent(in) :: knon, nsrf
24 guez 108 ! knon----input-I- nombre de points pour un type de surface
25     ! nsrf----input-I- indice pour le type de surface; voir indicesol.inc
26 guez 227 REAL, intent(in) :: speed(:), t(:), q(:), zgeop(:), psol(:) ! (knon)
27 guez 108 ! speed---input-R- module du vent au 1er niveau du modele
28     ! t-------input-R- temperature de l'air au 1er niveau du modele
29     ! q-------input-R- humidite de l'air au 1er niveau du modele
30     ! zgeop---input-R- geopotentiel au 1er niveau du modele
31 guez 227 ! psol----input-R- pression au sol
32     REAL, dimension(klon), intent(in) :: ts, qsurf, rugos
33 guez 108 ! ts------input-R- temperature de l'air a la surface
34     ! qsurf---input-R- humidite de l'air a la surface
35     ! rugos---input-R- rugosite
36 guez 227
37     REAL, dimension(klon), intent(out) :: cdram, cdrah, cdran, zri1, pref
38 guez 108 ! cdram--output-R- cdrag pour le moment
39     ! cdrah--output-R- cdrag pour les flux de chaleur latente et sensible
40     ! cdran--output-R- cdrag neutre
41     ! zri1---output-R- nb. Richardson entre la surface et la couche zgeop/RG
42     ! pref---output-R- pression au niveau zgeop/RG
43 guez 227
44     ! Local:
45 guez 108 REAL, parameter :: RKAR=0.40, CB=5.0, CC=5.0, CD=5.0
46     INTEGER :: i
47     REAL, dimension(klon) :: zdu2, zdphi, ztsolv, ztvd
48     REAL, dimension(klon) :: zscf, friv, frih, zucf, zcr
49     REAL, dimension(klon) :: zcfm1, zcfh1
50     REAL, dimension(klon) :: zcfm2, zcfh2
51     REAL, dimension(klon) :: trm0, trm1
52 guez 227
53 guez 108 !-------------------------------------------------------------------------
54 guez 227
55 guez 108 DO i = 1, knon
56 guez 3 zdphi(i) = zgeop(i)
57     zdu2(i) = speed(i)**2
58     pref(i) = exp(log(psol(i)) - zdphi(i)/(RD*t(i)* &
59 guez 227 (1.+ RETV * max(q(i), 0.0))))
60 guez 3 ztsolv(i) = ts(i)
61     ztvd(i) = t(i) * (psol(i)/pref(i))**RKAPPA
62 guez 227 trm0(i) = 1. + RETV * max(qsurf(i), 0.0)
63     trm1(i) = 1. + RETV * max(q(i), 0.0)
64 guez 3 ztsolv(i) = ztsolv(i) * trm0(i)
65     ztvd(i) = ztvd(i) * trm1(i)
66     zri1(i) = zdphi(i)*(ztvd(i)-ztsolv(i))/(zdu2(i)*ztvd(i))
67     cdran(i) = (RKAR/log(1.+zdphi(i)/(RG*rugos(i))))**2
68    
69 guez 227 IF (zri1(i) >= 0.) THEN
70     ! situation stable : pour eviter les inconsistances dans les cas
71 guez 108 ! tres stables on limite zri1 a 20. cf Hess et al. (1995)
72 guez 227 zri1(i) = min(20., zri1(i))
73     zscf(i) = SQRT(1.+CD*ABS(zri1(i)))
74     friv(i) = max(1. / (1.+2.*CB*zri1(i)/ zscf(i)), 0.1)
75     zcfm1(i) = cdran(i) * friv(i)
76     frih(i) = max(1./ (1.+3.*CB*zri1(i)*zscf(i)), 0.1)
77     zcfh1(i) = cdran(i) * frih(i)
78     cdram(i) = zcfm1(i)
79     cdrah(i) = zcfh1(i)
80 guez 3 ELSE
81 guez 108 ! situation instable
82 guez 227 zucf(i) = 1./(1.+3.0*CB*CC*cdran(i)*SQRT(ABS(zri1(i)) &
83     *(1.0+zdphi(i)/(RG*rugos(i)))))
84     zcfm2(i) = cdran(i)*max((1.-2.0*CB*zri1(i)*zucf(i)), 0.1)
85     zcfh2(i) = cdran(i)*max((1.-3.0*CB*zri1(i)*zucf(i)), 0.1)
86     cdram(i) = zcfm2(i)
87     cdrah(i) = zcfh2(i)
88    
89 guez 108 ! cdrah sur l'ocean cf. Miller et al. (1992)
90 guez 227
91 guez 108 zcr(i) = (0.0016/(cdran(i)*SQRT(zdu2(i))))*ABS(ztvd(i)-ztsolv(i)) &
92 guez 3 **(1./3.)
93 guez 227 IF (nsrf == is_oce) cdrah(i) = cdran(i)*(1.0+zcr(i)**1.25) &
94 guez 108 **(1./1.25)
95 guez 3 ENDIF
96 guez 108 END DO
97    
98     contains
99    
100     REAL function fsta(x)
101     real x
102     fsta = 1.0 / (1.0+10.0*x*(1+8.0*x))
103     end function fsta
104    
105     REAL function fins(x)
106     real x
107     fins = SQRT(1.0-18.0*x)
108     end function fins
109    
110     END SUBROUTINE coefcdrag
111    
112     end module coefcdrag_m

  ViewVC Help
Powered by ViewVC 1.1.21