/[lmdze]/trunk/dyn3d/exner_hyb.f
ViewVC logotype

Annotation of /trunk/dyn3d/exner_hyb.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 27 - (hide annotations)
Thu Mar 25 14:29:07 2010 UTC (14 years, 2 months ago) by guez
Original Path: trunk/libf/dyn3d/exner_hyb.f90
File size: 2896 byte(s)
"dyn3d" and "filtrez" do not contain any included file so make rules
have been updated.

"comdissip.f90" was useless, removed it.

"dynredem0" wrote undefined value in "controle(31)", that was
overwritten by "dynredem1". Now "dynredem0" just writes 0 to
"controle(31)".

Removed arguments of "inidissip". "inidissip" now accesses the
variables by use association.

In program "etat0_lim", "itaufin" is not defined so "dynredem1" wrote
undefined value to "controle(31)". Added argument "itau" of
"dynredem1" to correct that.

"itaufin" does not need to be a module variable (of "temps"), made it
a local variable of "leapfrog".

Removed calls to "diagedyn" from "leapfrog".

1 guez 3 module exner_hyb_m
2    
3     IMPLICIT NONE
4    
5     contains
6    
7     SUBROUTINE exner_hyb(ps, p, pks, pk, pkf)
8    
9     ! From dyn3d/exner_hyb.F, v 1.1.1.1 2004/05/19 12:53:07
10    
11 guez 10 ! Authors : P. Le Van, F. Hourdin
12 guez 3
13     ! Calcule la fonction d'Exner :
14     ! pk = Cp * p ** kappa
15 guez 10 ! aux milieux des "llm" couches.
16     ! "Pk(l)" est calculé au milieu de la couche "l", entre les pressions
17     ! "p(l)" et "p(l+1)", définies aux interfaces des couches.
18 guez 3
19     ! Au sommet de l'atmosphère :
20     ! p(llm+1) = 0.
21 guez 10 ! "ps" et "pks" sont la pression et la fonction d'Exner au sol.
22 guez 3
23     ! À partir des relations :
24    
25     ! -------- z
26 guez 10 !(1) p*dz(pk) = kappa * pk * dz(p)
27 guez 3
28 guez 10 !(2) pk(l) = alpha(l)+ beta(l) * pk(l-1)
29 guez 3
30 guez 10 ! (voir note de F. Hourdin), on détermine successivement, du haut
31 guez 3 ! vers le bas des couches, les coefficients :
32     ! alpha(llm), beta(llm)..., alpha(l), beta(l)..., alpha(2), beta(2)
33 guez 10 ! puis "pk(:, 1)".
34     ! Ensuite, on calcule, du bas vers le haut des couches, "pk(:, l)"
35 guez 3 ! donné par la relation (2), pour l = 2 à l = llm.
36    
37     use dimens_m, only: iim, jjm, llm
38     use comconst, only: kappa, cpp
39     use comvert, only: preff
40     use comgeom, only: aire_2d, apoln, apols
41 guez 27 use filtreg_m, only: filtreg
42 guez 3
43     REAL, intent(in):: ps((iim + 1) * (jjm + 1))
44     REAL, intent(in):: p((iim + 1) * (jjm + 1), llm + 1)
45    
46     real, intent(out):: pks((iim + 1) * (jjm + 1))
47     real, intent(out):: pk((iim + 1) * (jjm + 1), llm)
48     real, intent(out), optional:: pkf((iim + 1) * (jjm + 1), llm)
49    
50     ! Variables locales
51    
52     real alpha((iim + 1) * (jjm + 1), llm), beta((iim + 1) * (jjm + 1), llm)
53 guez 10 INTEGER l
54     REAL unpl2k, dellta((iim + 1) * (jjm + 1))
55 guez 3
56     REAL ppn(iim), pps(iim)
57    
58     !-------------------------------------
59    
60 guez 10 pks = cpp * (ps / preff)**kappa
61     ppn = aire_2d(:iim, 1) * pks(:iim)
62     pps = aire_2d(:iim, jjm + 1) &
63 guez 3 * pks(1 + (iim + 1) * jjm: iim + (iim + 1) * jjm)
64 guez 10 pks(:iim + 1) = SUM(ppn) /apoln
65     pks(1+(iim + 1) * jjm:) = SUM(pps) /apols
66 guez 3
67     unpl2k = 1. + 2 * kappa
68    
69 guez 10 ! Calcul des coefficients alpha et beta pour la couche l = llm :
70 guez 3 alpha(:, llm) = 0.
71 guez 10 beta(:, llm) = 1./ unpl2k
72 guez 3
73 guez 10 ! Calcul des coefficients alpha et beta pour l = llm-1 à l = 2 :
74     DO l = llm - 1, 2, -1
75     dellta = p(:, l) * unpl2k + p(:, l+1) * (beta(:, l+1) - unpl2k)
76     alpha(:, l) = - p(:, l+1) / dellta * alpha(:, l+1)
77     beta(:, l) = p(:, l) / dellta
78 guez 3 ENDDO
79    
80     ! Calcul de pk pour la couche 1, près du sol :
81 guez 10 pk(:, 1) = (p(:, 1) * pks - 0.5 * alpha(:, 2) * p(:, 2)) &
82 guez 3 / (p(:, 1) * (1. + kappa) + 0.5 * (beta(:, 2) - unpl2k) * p(:, 2))
83    
84 guez 10 ! Calcul de pk(:, l) pour l = 2 à l = llm :
85 guez 3 DO l = 2, llm
86 guez 10 pk(:, l) = alpha(:, l) + beta(:, l) * pk(:, l-1)
87 guez 3 ENDDO
88    
89     if (present(pkf)) then
90 guez 10 pkf = pk
91 guez 3 CALL filtreg(pkf, jjm + 1, llm, 2, 1, .TRUE., 1)
92     end if
93    
94     END SUBROUTINE exner_hyb
95    
96     end module exner_hyb_m

  ViewVC Help
Powered by ViewVC 1.1.21