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

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