source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn/convmas2_p.f @ 224

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 5.7 KB
Line 
1      SUBROUTINE convmas2_p ( convm )
2c
3      USE parallel_lmdz
4      IMPLICIT NONE
5
6c=======================================================================
7c
8c   Auteurs:  P. Le Van , F. Hourdin  .
9c   -------
10c
11c   Objet:
12c   ------
13c
14c   ********************************************************************
15c   .... calcul de la convergence du flux de masse aux niveaux p ...
16c   ********************************************************************
17c
18c
19c     pbaru  et  pbarv  sont des arguments d'entree pour le s-pg  ....
20c      .....  convm      est  un argument de sortie pour le s-pg  ....
21c
22c    le calcul se fait de haut en bas,
23c    la convergence de masse au niveau p(llm+1) est egale a 0. et
24c    n'est pas stockee dans le tableau convm .
25c
26c
27c=======================================================================
28c
29c   Declarations:
30c   -------------
31
32!-----------------------------------------------------------------------
33!   INCLUDE 'dimensions.h'
34!
35!   dimensions.h contient les dimensions du modele
36!   ndm est tel que iim=2**ndm
37!-----------------------------------------------------------------------
38
39      INTEGER iim,jjm,llm,ndm
40
41      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
42
43!-----------------------------------------------------------------------
44!
45! $Header$
46!
47!
48!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
49!                 veillez  n'utiliser que des ! pour les commentaires
50!                 et  bien positionner les & des lignes de continuation
51!                 (les placer en colonne 6 et en colonne 73)
52!
53!
54!-----------------------------------------------------------------------
55!   INCLUDE 'paramet.h'
56
57      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
58      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
59      INTEGER  ijmllm,mvar
60      INTEGER jcfil,jcfllm
61
62      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
63     &    ,jjp1=jjm+1-1/jjm)
64      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
65      PARAMETER( kftd  = iim/2 -ndm )
66      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
67      PARAMETER( ip1jmi1= ip1jm - iip1 )
68      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
69      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
70      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
71
72!-----------------------------------------------------------------------
73!
74! $Id: comvert.h 1654 2012-09-24 15:07:18Z aslmd $
75!
76!-----------------------------------------------------------------------
77!   INCLUDE 'comvert.h'
78
79      COMMON/comvertr/ap(llm+1),bp(llm+1),presnivs(llm),dpres(llm),     &
80     &               pa,preff,nivsigs(llm),nivsig(llm+1),               &
81     &               aps(llm),bps(llm),scaleheight,pseudoalt(llm)
82
83      common/comverti/disvert_type, pressure_exner
84
85      real ap     ! hybrid pressure contribution at interlayers
86      real bp     ! hybrid sigma contribution at interlayer
87      real presnivs ! (reference) pressure at mid-layers
88      real dpres
89      real pa     ! reference pressure (Pa) at which hybrid coordinates
90                  ! become purely pressure
91      real preff  ! reference surface pressure (Pa)
92      real nivsigs
93      real nivsig
94      real aps    ! hybrid pressure contribution at mid-layers
95      real bps    ! hybrid sigma contribution at mid-layers
96      real scaleheight ! atmospheric (reference) scale height (km)
97      real pseudoalt ! pseudo-altitude of model levels (km), based on presnivs(),
98                     ! preff and scaleheight
99
100      integer disvert_type ! type of vertical discretization:
101                           ! 1: Earth (default for planet_type==earth),
102                           !     automatic generation
103                           ! 2: Planets (default for planet_type!=earth),
104                           !     using 'z2sig.def' (or 'esasig.def) file
105
106      logical pressure_exner
107!     compute pressure inside layers using Exner function, else use mean
108!     of pressure values at interfaces
109
110 !-----------------------------------------------------------------------
111!
112! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
113!
114!
115! NB: keep items of different kinds in seperate common blocs to avoid
116!     "misaligned commons" issues
117!-----------------------------------------------------------------------
118! INCLUDE 'logic.h'
119
120      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
121     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
122     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
123     &  ,ok_limit,ok_etat0,hybrid                                       &
124     &  ,moyzon_mu,moyzon_ch
125
126      COMMON/logici/ iflag_phys,iflag_trac
127     
128      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
129     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
130     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
131     &  ,ok_limit,ok_etat0
132      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
133                     ! (only used if disvert_type==2)
134      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
135
136      integer iflag_phys,iflag_trac
137!$OMP THREADPRIVATE(/logicl/)
138!$OMP THREADPRIVATE(/logici/)
139!-----------------------------------------------------------------------
140
141      REAL pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm )
142      REAL :: convm(  ip1jmp1,llm )
143      INTEGER   l,ij
144      INTEGER ijb,ije,jjb,jje
145 
146c$OMP MASTER
147c    integration de la convergence de masse de haut  en bas ......
148       ijb=ij_begin
149       ije=ij_end+iip1
150       if (pole_sud) ije=ij_end
151           
152      DO      l      = llmm1, 1, -1
153        DO    ij     = ijb, ije
154         convm(ij,l) = convm(ij,l) + convm(ij,l+1)
155        ENDDO
156      ENDDO
157c
158c$OMP END MASTER
159      RETURN
160      END
Note: See TracBrowser for help on using the repository browser.