source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn3d_common/geopot.f @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 4.7 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE geopot (ngrid, teta, pk, pks, phis, phi )
5      IMPLICIT NONE
6
7c=======================================================================
8c
9c   Auteur:  P. Le Van
10c   -------
11c
12c   Objet:
13c   ------
14c
15c    *******************************************************************
16c    ....   calcul du geopotentiel aux milieux des couches    .....
17c    *******************************************************************
18c
19c     ....   l'integration se fait de bas en haut  ....
20c
21c     .. ngrid,teta,pk,pks,phis sont des argum. d'entree pour le s-pg ..
22c              phi               est un  argum. de sortie pour le s-pg .
23c
24c=======================================================================
25c-----------------------------------------------------------------------
26c   Declarations:
27c   -------------
28
29!-----------------------------------------------------------------------
30!   INCLUDE 'dimensions.h'
31!
32!   dimensions.h contient les dimensions du modele
33!   ndm est tel que iim=2**ndm
34!-----------------------------------------------------------------------
35
36      INTEGER iim,jjm,llm,ndm
37
38      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
39
40!-----------------------------------------------------------------------
41!
42! $Header$
43!
44!
45!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
46!                 veillez  n'utiliser que des ! pour les commentaires
47!                 et  bien positionner les & des lignes de continuation
48!                 (les placer en colonne 6 et en colonne 73)
49!
50!
51!-----------------------------------------------------------------------
52!   INCLUDE 'paramet.h'
53
54      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
55      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
56      INTEGER  ijmllm,mvar
57      INTEGER jcfil,jcfllm
58
59      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
60     &    ,jjp1=jjm+1-1/jjm)
61      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
62      PARAMETER( kftd  = iim/2 -ndm )
63      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
64      PARAMETER( ip1jmi1= ip1jm - iip1 )
65      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
66      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
67      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
68
69!-----------------------------------------------------------------------
70!
71! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $
72!
73!-----------------------------------------------------------------------
74!   INCLUDE 'comvert.h'
75
76      COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),     &
77     &               pa,preff,nivsigs(llm),nivsig(llm+1),               &
78     &               aps(llm),bps(llm),scaleheight,pseudoalt(llm)
79
80      common/comverti/disvert_type, pressure_exner
81
82      real ap     ! hybrid pressure contribution at interlayers
83      real bp     ! hybrid sigma contribution at interlayer
84      real presnivs ! (reference) pressure at mid-layers
85      real dpres
86      real pa     ! reference pressure (Pa) at which hybrid coordinates
87                  ! become purely pressure
88      real preff  ! reference surface pressure (Pa)
89      real nivsigs
90      real nivsig
91      real aps    ! hybrid pressure contribution at mid-layers
92      real bps    ! hybrid sigma contribution at mid-layers
93      real scaleheight ! atmospheric (reference) scale height (km)
94      real pseudoalt ! pseudo-altitude of model levels (km), based on presnivs(),
95                     ! preff and scaleheight
96
97      integer disvert_type ! type of vertical discretization:
98                           ! 1: Earth (default for planet_type==earth),
99                           !     automatic generation
100                           ! 2: Planets (default for planet_type!=earth),
101                           !     using 'z2sig.def' (or 'esasig.def) file
102
103      logical pressure_exner
104!     compute pressure inside layers using Exner function, else use mean
105!     of pressure values at interfaces
106
107 !-----------------------------------------------------------------------
108
109c   Arguments:
110c   ----------
111
112      INTEGER ngrid
113      REAL teta(ngrid,llm),pks(ngrid),phis(ngrid),pk(ngrid,llm) ,
114     *       phi(ngrid,llm)
115
116
117c   Local:
118c   ------
119
120      INTEGER  l, ij
121
122
123c-----------------------------------------------------------------------
124c     calcul de phi au niveau 1 pres du sol  .....
125
126      DO   1  ij  = 1, ngrid
127      phi( ij,1 ) = phis( ij ) + teta(ij,1) * ( pks(ij) - pk(ij,1) )
128   1  CONTINUE
129
130c     calcul de phi aux niveaux superieurs  .......
131
132      DO  l = 2,llm
133        DO  ij    = 1,ngrid
134        phi(ij,l) = phi(ij,l-1) + 0.5 * ( teta(ij,l)  + teta(ij,l-1) ) 
135     *                              *   (  pk(ij,l-1) -  pk(ij,l)    )
136        ENDDO
137      ENDDO
138
139      RETURN
140      END
Note: See TracBrowser for help on using the repository browser.