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

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

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

trunk/libf/dyn3d/exner_hyb.f90 revision 40 by guez, Tue Feb 22 13:49:36 2011 UTC trunk/dyn3d/exner_hyb.f revision 83 by guez, Thu Mar 6 15:12:00 2014 UTC
# Line 6  contains Line 6  contains
6    
7    SUBROUTINE exner_hyb(ps, p, pks, pk, pkf)    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      ! From dyn3d/exner_hyb.F, version 1.1.1.1 2004/05/19 12:53:07
   
10      ! Authors: P. Le Van, F. Hourdin      ! Authors: P. Le Van, F. Hourdin
11    
12      ! Calcule la fonction d'Exner :      ! Calcule la fonction d'Exner :
# Line 17  contains Line 16  contains
16      ! "p(l)" et "p(l+1)", définies aux interfaces des couches.      ! "p(l)" et "p(l+1)", définies aux interfaces des couches.
17    
18      ! Au sommet de l'atmosphère :      ! Au sommet de l'atmosphère :
19      ! p(llm+1) = 0.      ! p(llm+1) = 0
20      ! "ps" et "pks" sont la pression et la fonction d'Exner au sol.      ! "ps" et "pks" sont la pression et la fonction d'Exner au sol.
21    
22      ! À partir des relations :      ! À partir des relations :
23      !(1) \overline{p * \delta_z pk}^z = kappa * pk * \delta_z p      !(1) \overline{p * \delta_z pk}^z = kappa * pk * \delta_z p
24      !(2) pk(l) = beta(l) * pk(l-1)      !(2) pk(l) = beta(l) * pk(l-1)
25      ! (cf. documentation), on détermine successivement, du haut vers      ! (cf. documentation), on détermine successivement, du haut vers
26      ! le bas des couches, les coefficients : beta(llm)..., beta(l)...,      ! le bas des couches, les coefficients : beta(llm), ..., beta(l), ...,
27      ! beta(2) puis "pk(:, :, 1)". Ensuite, on calcule, du bas vers le      ! beta(2) puis "pk(:, :, 1)". Ensuite, on calcule, du bas vers le
28      ! haut des couches, "pk(:, :, l)" donné par la relation (2), pour      ! haut des couches, "pk(:, :, l)" donné par la relation (2), pour
29      ! l = 2 à l = llm.      ! l = 2 à l = llm.
30    
31      use dimens_m, only: iim, jjm, llm      use dimens_m, only: iim, jjm, llm
32      use comconst, only: kappa, cpp      use comconst, only: kappa, cpp
33      use comvert, only: preff      use disvert_m, only: preff
34      use comgeom, only: aire_2d, apoln, apols      use comgeom, only: aire_2d, apoln, apols
35      use filtreg_m, only: filtreg      use filtreg_m, only: filtreg
36    
# Line 42  contains Line 41  contains
41      real, intent(out):: pk(iim + 1, jjm + 1, llm)      real, intent(out):: pk(iim + 1, jjm + 1, llm)
42      real, intent(out), optional:: pkf(iim + 1, jjm + 1, llm)      real, intent(out), optional:: pkf(iim + 1, jjm + 1, llm)
43    
44      ! Variables locales      ! Variables locales :
45      real beta(iim + 1, jjm + 1, 2:llm)      real beta(iim + 1, jjm + 1, 2:llm)
46      INTEGER l      INTEGER l
47      REAL unpl2k      REAL unpl2k
# Line 60  contains Line 59  contains
59              / (p(:, :, l) * unpl2k + p(:, :, l+1) * (beta(:, :, l+1) - unpl2k))              / (p(:, :, l) * unpl2k + p(:, :, l+1) * (beta(:, :, l+1) - unpl2k))
60      ENDDO      ENDDO
61    
62      pk(:, :, 1) = p(:, :, 1) * pks  &      pk(:, :, 1) = ps * pks &
63           / (p(:, :, 1) * (1. + kappa) &           / (ps * (1. + kappa) + 0.5 * (beta(:, :, 2) - unpl2k) * p(:, :, 2))
          + 0.5 * (beta(:, :, 2) - unpl2k) * p(:, :, 2))  
64      DO l = 2, llm      DO l = 2, llm
65         pk(:, :, l) = beta(:, :, l) * pk(:, :, l-1)         pk(:, :, l) = beta(:, :, l) * pk(:, :, l - 1)
66      ENDDO      ENDDO
67    
68      if (present(pkf)) then      if (present(pkf)) then
69         pkf = pk         pkf = pk
70         CALL filtreg(pkf, jjm + 1, llm, 2, 1, .TRUE., 1)         CALL filtreg(pkf, jjm + 1, llm, 2, 1, .TRUE.)
71      end if      end if
72    
73    END SUBROUTINE exner_hyb    END SUBROUTINE exner_hyb

Legend:
Removed from v.40  
changed lines
  Added in v.83

  ViewVC Help
Powered by ViewVC 1.1.21