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

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

Parent Directory Parent Directory | Revision Log Revision Log


Revision 47 - (show annotations)
Fri Jul 1 15:00:48 2011 UTC (12 years, 10 months ago) by guez
File size: 3274 byte(s)
Split "thermcell.f" and "cv3_routines.f".
Removed copies of files that are now in "L_util".
Moved "mva9" and "diagetpq" to their own files.
Unified variable names across procedures.

1 module coefkzmin_m
2
3 IMPLICIT NONE
4
5 contains
6
7 SUBROUTINE coefkzmin(ngrid, ypaprs, ypplay, yu, yv, yt, yq, ycoefm, km, kn)
8
9 ! From LMDZ4/libf/phylmd/coefkzmin.F, version 1.1.1.1 2004/05/19 12:53:08
10
11 ! Entrées modifiées en attendant une version où les zlev et zlay
12 ! soient disponibles.
13
14 USE dimphy, ONLY: klev, klon
15 USE suphec_m, ONLY: rd, rg, rkappa
16
17 integer, intent(in):: ngrid
18 REAL, intent(in):: ypaprs(klon, klev+1), ypplay(klon, klev)
19 REAL, intent(in):: yu(klon, klev), yv(klon, klev) ! wind, in m s-1
20 REAL, intent(in):: yt(klon, klev) ! temperature, in K
21 REAL, intent(in):: yq(klon, klev)
22
23 REAL, intent(in):: ycoefm(klon) ! drag coefficient
24
25 REAL, intent(inout):: km(klon, klev)
26 ! coefficient de diffusion turbulente de quantité de mouvement (au
27 ! bas de chaque couche) (en sortie : la valeur à la fin du pas de
28 ! temps), m2 s-1
29
30 REAL, intent(inout):: kn(klon, klev)
31 ! coefficient de diffusion turbulente des scalaires (au bas de
32 ! chaque couche) (en sortie : la valeur à la fin du pas de temps), m2 s-1
33
34 ! Local:
35
36 real ustar(ngrid) ! u*
37 real zlay(ngrid, klev) ! in m
38 integer i, k
39 real pblhmin(ngrid)
40 real, parameter:: coriol = 1e-4
41
42 REAL zlev(ngrid, 2: klev)
43 ! altitude at level (interface between layer with same index), in m
44
45 REAL teta(ngrid, klev)
46 ! température potentielle au centre de chaque couche (la valeur au
47 ! debut du pas de temps)
48
49 real, PARAMETER:: kap = 0.4
50
51 !---------------------------------------------------------------------
52
53 ! Debut de la partie qui doit etre incluse a terme dans clmain.
54
55 do i = 1, ngrid
56 zlay(i, 1) = RD * yt(i, 1) * 2 / (ypaprs(i, 1) + ypplay(i, 1)) &
57 * (ypaprs(i, 1) - ypplay(i, 1)) / RG
58 enddo
59
60 do k = 2, klev
61 do i = 1, ngrid
62 zlay(i, k) = zlay(i, k-1) + RD * 0.5 * (yt(i, k - 1) + yt(i, k)) &
63 / ypaprs(i, k) * (ypplay(i, k - 1) - ypplay(i, k)) / RG
64 enddo
65 enddo
66
67 do k=1, klev
68 do i = 1, ngrid
69 ! Attention : on passe la temperature potentielle virtuelle
70 ! pour le calcul de K.
71 teta(i, k) = yt(i, k) * (ypaprs(i, 1) / ypplay(i, k))**rkappa &
72 * (1. + 0.61 * yq(i, k))
73 enddo
74 enddo
75
76 forall (k = 2: klev) zlev(:, k) = 0.5 * (zlay(:, k) + zlay(:, k-1))
77 ustar = SQRT(ycoefm(:ngrid) * (yu(:ngrid, 1)**2 + yv(:ngrid, 1)**2))
78
79 ! Fin de la partie qui doit être incluse à terme dans clmain
80
81 ! Cette routine est ecrite pour avoir en entree ustar, teta et zlev
82 ! Ici, on a inclus le calcul de ces trois variables dans la routine
83 ! coefkzmin en attendant une nouvelle version de la couche limite
84 ! ou ces variables seront disponibles.
85
86 ! Debut de la routine coefkzmin proprement dite
87
88 pblhmin = 0.07 * ustar / coriol
89
90 do k = 2, klev
91 do i = 1, ngrid
92 if (teta(i, 2) > teta(i, 1)) then
93 kn(i, k) = kap * zlev(i, k) * ustar(i) &
94 * (max(1. - zlev(i, k) / pblhmin(i), 0.))**2
95 else
96 kn(i, k) = 0. ! min n'est utilisé que pour les SL stables
97 endif
98 km(i, k) = kn(i, k)
99 enddo
100 enddo
101
102 end SUBROUTINE coefkzmin
103
104 end module coefkzmin_m

  ViewVC Help
Powered by ViewVC 1.1.21