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

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 4.0 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE bernoui (ngrid,nlay,pphi,pecin,pbern)
5      IMPLICIT NONE
6
7c=======================================================================
8c
9c   Auteur:   P. Le Van
10c   -------
11c
12c   Objet:
13c   ------
14c     calcul de la fonction de Bernouilli aux niveaux s  .....
15c     phi  et  ecin  sont des arguments d'entree pour le s-pg .......
16c          bern       est un  argument de sortie pour le s-pg  ......
17c
18c    fonction de Bernouilli = bern = filtre de( geopotentiel +
19c                              energ.cinet.)
20c
21c=======================================================================
22c
23c-----------------------------------------------------------------------
24c   Decalrations:
25c   -------------
26c
27!-----------------------------------------------------------------------
28!   INCLUDE 'dimensions.h'
29!
30!   dimensions.h contient les dimensions du modele
31!   ndm est tel que iim=2**ndm
32!-----------------------------------------------------------------------
33
34      INTEGER iim,jjm,llm,ndm
35
36      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
37
38!-----------------------------------------------------------------------
39!
40! $Header$
41!
42!
43!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
44!                 veillez  n'utiliser que des ! pour les commentaires
45!                 et  bien positionner les & des lignes de continuation
46!                 (les placer en colonne 6 et en colonne 73)
47!
48!
49!-----------------------------------------------------------------------
50!   INCLUDE 'paramet.h'
51
52      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
53      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
54      INTEGER  ijmllm,mvar
55      INTEGER jcfil,jcfllm
56
57      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
58     &    ,jjp1=jjm+1-1/jjm)
59      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
60      PARAMETER( kftd  = iim/2 -ndm )
61      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
62      PARAMETER( ip1jmi1= ip1jm - iip1 )
63      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
64      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
65      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
66
67!-----------------------------------------------------------------------
68!
69! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
70!
71!
72! NB: keep items of different kinds in seperate common blocs to avoid
73!     "misaligned commons" issues
74!-----------------------------------------------------------------------
75! INCLUDE 'logic.h'
76
77      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
78     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
79     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
80     &  ,ok_limit,ok_etat0,hybrid                                       &
81     &  ,moyzon_mu,moyzon_ch
82
83      COMMON/logici/ iflag_phys,iflag_trac
84     
85      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
86     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
87     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
88     &  ,ok_limit,ok_etat0
89      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
90                     ! (only used if disvert_type==2)
91      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
92
93      integer iflag_phys,iflag_trac
94!$OMP THREADPRIVATE(/logicl/)
95!$OMP THREADPRIVATE(/logici/)
96!-----------------------------------------------------------------------
97c
98c   Arguments:
99c   ----------
100c
101      INTEGER nlay,ngrid
102      REAL pphi(ngrid*nlay),pecin(ngrid*nlay),pbern(ngrid*nlay)
103c
104c   Local:
105c   ------
106c
107      INTEGER   ijl
108c
109c-----------------------------------------------------------------------
110c   calcul de Bernouilli:
111c   ---------------------
112c
113      DO 4 ijl = 1,ngrid*nlay
114         pbern( ijl ) =  pphi( ijl ) + pecin( ijl )
115   4  CONTINUE
116c
117c-----------------------------------------------------------------------
118c   filtre:
119c   -------
120c
121      CALL filtreg( pbern, jjp1, llm, 2,1, .true., 1 )
122c
123c-----------------------------------------------------------------------
124      RETURN
125      END
Note: See TracBrowser for help on using the repository browser.