/[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 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/Sources/dyn3d/exner_hyb.f revision 137 by guez, Wed May 6 15:51:03 2015 UTC
# Line 4  module exner_hyb_m Line 4  module exner_hyb_m
4    
5  contains  contains
6    
7    SUBROUTINE exner_hyb(ps, p, pks, pk, pkf)    SUBROUTINE exner_hyb(ps, p, pks, pk)
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
     ! Auteurs :  P. Le Van, F. Hourdin.  
11    
12      ! Calcule la fonction d'Exner :      ! Calcule la fonction d'Exner :
13      ! pk = Cp * p ** kappa      ! pk = Cp * p ** kappa
14      ! aux milieux des couches.      ! aux milieux des "llm" couches.
15      ! Pk(l) est calculé aux milieux des couches "l", entre les pressions      ! "Pk(l)" est calcul\'e au milieu de la couche "l", entre les pressions
16      ! "p(l)" et "p(l+1)", définies aux interfaces des "llm" couches.      ! "p(l)" et "p(l+1)", d\'efinies aux interfaces des couches.
17    
18      ! Au sommet de l'atmosphère :      ! Au sommet de l'atmosph\`ere :
19      ! p(llm+1) = 0.      ! p(llm+1) = 0
20      ! et 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 :      ! \`A partir des relations :
23        !(1) \overline{p * \delta_z pk}^z = kappa * pk * \delta_z p
24      !   -------- z      !(2) pk(l) = beta(l) * pk(l-1)
25      !(1) p*dz(pk) = kappa *pk*dz(p)      ! (cf. documentation), on d\'etermine successivement, du haut vers
26        ! le bas des couches, les coefficients : beta(llm), ..., beta(l), ...,
27      !(2) pk(l) = alpha(l)+ beta(l)*pk(l-1)      ! beta(2) puis "pk(:, :, 1)". Ensuite, on calcule, du bas vers le
28        ! haut des couches, "pk(:, :, l)" donn\'e par la relation (2), pour
29      ! (voir note de F. Hourdin), on determine successivement, du haut      ! l = 2 \`a l = llm.
     ! vers le bas des couches, les coefficients :  
     ! alpha(llm), beta(llm)..., alpha(l), beta(l)..., alpha(2), beta(2)  
     ! puis "pk(ij, 1)".  
     ! Ensuite, on calcule, du bas vers le haut des couches, "pk(ij, l)"  
     ! donné par la relation (2), pour l = 2 à l = llm.  
30    
31      use dimens_m, only: iim, jjm, llm      use dimens_m, only: llm
32      use comconst, only: kappa, cpp      use comconst, only: kappa, cpp
33      use comvert, only: preff      use disvert_m, only: preff
     use comgeom, only: aire_2d, apoln, apols  
34    
35      REAL, intent(in):: ps((iim + 1) * (jjm + 1))      REAL, intent(in):: ps(:, :) ! (longitude, latitude)
36      REAL, intent(in):: p((iim + 1) * (jjm + 1), llm + 1)      REAL, intent(in):: p(:, :, :) ! (longitude, latitude, llm + 1)
37    
38      real, intent(out):: pks((iim + 1) * (jjm + 1))      real, intent(out):: pks(:, :) ! (longitude, latitude)
39      real, intent(out):: pk((iim + 1) * (jjm + 1), llm)      real, intent(out):: pk(:, :, :) ! (longitude, latitude, llm)
     real, intent(out), optional:: pkf((iim + 1) * (jjm + 1), llm)  
40    
41      ! Variables locales      ! Variables locales :
42        real beta(size(ps, 1), size(ps, 2), 2:llm)
43      real alpha((iim + 1) * (jjm + 1), llm), beta((iim + 1) * (jjm + 1), llm)      INTEGER l
44      INTEGER l, ij      REAL unpl2k
     REAL unpl2k, dellta  
   
     REAL ppn(iim), pps(iim)  
     REAL xpn, xps  
     REAL SSUM  
45    
46      !-------------------------------------      !-------------------------------------
47    
48      pks(:) = cpp * (ps(:) / preff)**kappa      pks = cpp * (ps / preff)**kappa
     ppn(:) = aire_2d(:iim, 1) * pks(:iim)  
     pps(:) = aire_2d(:iim, jjm + 1) &  
          * pks(1 + (iim + 1) * jjm: iim + (iim + 1) * jjm)  
     xpn = SSUM(iim, ppn, 1) /apoln  
     xps = SSUM(iim, pps, 1) /apols  
     pks(:iim + 1) = xpn  
     pks(1+(iim + 1) * jjm:) = xps  
   
49      unpl2k = 1. + 2 * kappa      unpl2k = 1. + 2 * kappa
50    
51      ! Calcul des coeff. alpha et beta  pour la couche l = llm      beta(:, :, llm) = 1. / unpl2k
52      alpha(:, llm) = 0.      DO l = llm - 1, 2, -1
53      beta (:, llm) = 1./ unpl2k         beta(:, :, l) = p(:, :, l) &
54                / (p(:, :, l) * unpl2k + p(:, :, l+1) * (beta(:, :, l+1) - unpl2k))
     ! Calcul des coeff. alpha et beta  pour l = llm-1  à l = 2  
     DO l = llm -1 , 2 , -1  
        DO ij = 1, (iim + 1) * (jjm + 1)  
           dellta = p(ij, l)* unpl2k + p(ij, l+1)* ( beta(ij, l+1)-unpl2k )  
           alpha(ij, l)  = - p(ij, l+1) / dellta * alpha(ij, l+1)  
           beta (ij, l)  =   p(ij, l  ) / dellta    
        ENDDO  
55      ENDDO      ENDDO
56    
57      ! Calcul de pk pour la couche 1, près du sol :      pk(:, :, 1) = ps * pks &
58      pk(:, 1) = (p(:, 1) * pks(:) - 0.5 * alpha(:, 2) * p(:, 2))  &           / (ps * (1. + kappa) + 0.5 * (beta(:, :, 2) - unpl2k) * p(:, :, 2))
          / (p(:, 1) * (1. + kappa) + 0.5 * (beta(:, 2) - unpl2k) * p(:, 2))  
   
     ! Calcul de pk(ij, l) , pour l = 2 à l = llm  
59      DO l = 2, llm      DO l = 2, llm
60         DO   ij   = 1, (iim + 1) * (jjm + 1)         pk(:, :, l) = beta(:, :, l) * pk(:, :, l - 1)
           pk(ij, l) = alpha(ij, l) + beta(ij, l) * pk(ij, l-1)  
        ENDDO  
61      ENDDO      ENDDO
62    
     if (present(pkf)) then  
        pkf(:, :) = pk(:, :)  
        CALL filtreg(pkf, jjm + 1, llm, 2, 1, .TRUE., 1)  
     end if  
   
63    END SUBROUTINE exner_hyb    END SUBROUTINE exner_hyb
64    
65  end module exner_hyb_m  end module exner_hyb_m

Legend:
Removed from v.3  
changed lines
  Added in v.137

  ViewVC Help
Powered by ViewVC 1.1.21