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

Annotation of /trunk/Sources/dyn3d/exner_hyb.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 137 - (hide annotations)
Wed May 6 15:51:03 2015 UTC (9 years ago) by guez
File size: 1986 byte(s)
Removed unused argument missval in ma_fucoll_r[1-3]1, ma_fufill_r[1-3]1.

Split filtreg into two procedures: filtreg_scal and filtreg_v. I did
not like the test on the extent of the argument and there was no
common code between the two cases: jjm and jjm + 1. Also, it is
simpler now to just remove the argument "direct" from filtreg_v instead
of allowing it and then stopping the program if it is false.

Removed the computation of pkf in reanalyse2nat, was not used.

As a consequence of the split of filtreg, had to extract the
computation of pkf out of exner_hyb. This is clearer anyway because we
want to be able to call exner_hyb with any size in the first two
dimensions (as in test_disvert). But at the same time exner_hyb
required particular sizes for the computation of pkf. It was
awkward. The only computation of pkf is now in leapfrog.

1 guez 3 module exner_hyb_m
2    
3     IMPLICIT NONE
4    
5     contains
6    
7 guez 137 SUBROUTINE exner_hyb(ps, p, pks, pk)
8 guez 3
9 guez 88 ! From dyn3d/exner_hyb.F, version 1.1.1.1, 2004/05/19 12:53:07
10 guez 40 ! Authors: P. Le Van, F. Hourdin
11 guez 3
12     ! Calcule la fonction d'Exner :
13     ! pk = Cp * p ** kappa
14 guez 10 ! aux milieux des "llm" couches.
15 guez 137 ! "Pk(l)" est calcul\'e au milieu de la couche "l", entre les pressions
16     ! "p(l)" et "p(l+1)", d\'efinies aux interfaces des couches.
17 guez 3
18 guez 137 ! Au sommet de l'atmosph\`ere :
19 guez 48 ! p(llm+1) = 0
20 guez 10 ! "ps" et "pks" sont la pression et la fonction d'Exner au sol.
21 guez 3
22 guez 137 ! \`A partir des relations :
23 guez 40 !(1) \overline{p * \delta_z pk}^z = kappa * pk * \delta_z p
24     !(2) pk(l) = beta(l) * pk(l-1)
25 guez 137 ! (cf. documentation), on d\'etermine successivement, du haut vers
26 guez 48 ! le bas des couches, les coefficients : beta(llm), ..., beta(l), ...,
27 guez 40 ! beta(2) puis "pk(:, :, 1)". Ensuite, on calcule, du bas vers le
28 guez 137 ! haut des couches, "pk(:, :, l)" donn\'e par la relation (2), pour
29     ! l = 2 \`a l = llm.
30 guez 3
31 guez 91 use dimens_m, only: llm
32 guez 3 use comconst, only: kappa, cpp
33 guez 66 use disvert_m, only: preff
34 guez 3
35 guez 91 REAL, intent(in):: ps(:, :) ! (longitude, latitude)
36     REAL, intent(in):: p(:, :, :) ! (longitude, latitude, llm + 1)
37 guez 3
38 guez 91 real, intent(out):: pks(:, :) ! (longitude, latitude)
39     real, intent(out):: pk(:, :, :) ! (longitude, latitude, llm)
40 guez 3
41 guez 48 ! Variables locales :
42 guez 91 real beta(size(ps, 1), size(ps, 2), 2:llm)
43 guez 10 INTEGER l
44 guez 40 REAL unpl2k
45 guez 3
46     !-------------------------------------
47    
48 guez 10 pks = cpp * (ps / preff)**kappa
49 guez 3 unpl2k = 1. + 2 * kappa
50    
51 guez 40 beta(:, :, llm) = 1. / unpl2k
52 guez 10 DO l = llm - 1, 2, -1
53 guez 40 beta(:, :, l) = p(:, :, l) &
54     / (p(:, :, l) * unpl2k + p(:, :, l+1) * (beta(:, :, l+1) - unpl2k))
55 guez 3 ENDDO
56    
57 guez 83 pk(:, :, 1) = ps * pks &
58     / (ps * (1. + kappa) + 0.5 * (beta(:, :, 2) - unpl2k) * p(:, :, 2))
59 guez 3 DO l = 2, llm
60 guez 83 pk(:, :, l) = beta(:, :, l) * pk(:, :, l - 1)
61 guez 3 ENDDO
62    
63     END SUBROUTINE exner_hyb
64    
65     end module exner_hyb_m

  ViewVC Help
Powered by ViewVC 1.1.21