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

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 6.4 KB
Line 
1!
2! $Header$
3!
4      SUBROUTINE divgrad (klevel,h, lh, divgra )
5      IMPLICIT NONE
6c
7c=======================================================================
8c
9c  Auteur :   P. Le Van
10c  ----------
11c
12c                              lh
13c      calcul de  (div( grad ))   de h  .....
14c      h  et lh  sont des arguments  d'entree pour le s-prog
15c      divgra     est  un argument  de sortie pour le s-prog
16c
17c=======================================================================
18c
19c   declarations:
20c   -------------
21c
22!-----------------------------------------------------------------------
23!   INCLUDE 'dimensions.h'
24!
25!   dimensions.h contient les dimensions du modele
26!   ndm est tel que iim=2**ndm
27!-----------------------------------------------------------------------
28
29      INTEGER iim,jjm,llm,ndm
30
31      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
32
33!-----------------------------------------------------------------------
34!
35! $Header$
36!
37!
38!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
39!                 veillez  n'utiliser que des ! pour les commentaires
40!                 et  bien positionner les & des lignes de continuation
41!                 (les placer en colonne 6 et en colonne 73)
42!
43!
44!-----------------------------------------------------------------------
45!   INCLUDE 'paramet.h'
46
47      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
48      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
49      INTEGER  ijmllm,mvar
50      INTEGER jcfil,jcfllm
51
52      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
53     &    ,jjp1=jjm+1-1/jjm)
54      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
55      PARAMETER( kftd  = iim/2 -ndm )
56      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
57      PARAMETER( ip1jmi1= ip1jm - iip1 )
58      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
59      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
60      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
61
62!-----------------------------------------------------------------------
63!
64! $Header$
65!
66!CDK comgeom
67      COMMON/comgeom/                                                   &
68     & cu(ip1jmp1),cv(ip1jm),unscu2(ip1jmp1),unscv2(ip1jm),             &
69     & aire(ip1jmp1),airesurg(ip1jmp1),aireu(ip1jmp1),                  &
70     & airev(ip1jm),unsaire(ip1jmp1),apoln,apols,                       &
71     & unsairez(ip1jm),airuscv2(ip1jm),airvscu2(ip1jm),                 &
72     & aireij1(ip1jmp1),aireij2(ip1jmp1),aireij3(ip1jmp1),              &
73     & aireij4(ip1jmp1),alpha1(ip1jmp1),alpha2(ip1jmp1),                &
74     & alpha3(ip1jmp1),alpha4(ip1jmp1),alpha1p2(ip1jmp1),               &
75     & alpha1p4(ip1jmp1),alpha2p3(ip1jmp1),alpha3p4(ip1jmp1),           &
76     & fext(ip1jm),constang(ip1jmp1),rlatu(jjp1),rlatv(jjm),            &
77     & rlonu(iip1),rlonv(iip1),cuvsurcv(ip1jm),cvsurcuv(ip1jm),         &
78     & cvusurcu(ip1jmp1),cusurcvu(ip1jmp1),cuvscvgam1(ip1jm),           &
79     & cuvscvgam2(ip1jm),cvuscugam1(ip1jmp1),                           &
80     & cvuscugam2(ip1jmp1),cvscuvgam(ip1jm),cuscvugam(ip1jmp1),         &
81     & unsapolnga1,unsapolnga2,unsapolsga1,unsapolsga2,                 &
82     & unsair_gam1(ip1jmp1),unsair_gam2(ip1jmp1),unsairz_gam(ip1jm),    &
83     & aivscu2gam(ip1jm),aiuscv2gam(ip1jm),xprimu(iip1),xprimv(iip1)
84
85!
86        REAL                                                            &
87     & cu,cv,unscu2,unscv2,aire,airesurg,aireu,airev,unsaire,apoln     ,&
88     & apols,unsairez,airuscv2,airvscu2,aireij1,aireij2,aireij3,aireij4,&
89     & alpha1,alpha2,alpha3,alpha4,alpha1p2,alpha1p4,alpha2p3,alpha3p4 ,&
90     & fext,constang,rlatu,rlatv,rlonu,rlonv,cuvscvgam1,cuvscvgam2     ,&
91     & cvuscugam1,cvuscugam2,cvscuvgam,cuscvugam,unsapolnga1,unsapolnga2&
92     & ,unsapolsga1,unsapolsga2,unsair_gam1,unsair_gam2,unsairz_gam    ,&
93     & aivscu2gam ,aiuscv2gam,cuvsurcv,cvsurcuv,cvusurcu,cusurcvu,xprimu&
94     & , xprimv
95!
96!
97! $Header$
98!
99!  Attention : ce fichier include est compatible format fixe/format libre
100!                 veillez à n'utiliser que des ! pour les commentaires
101!                 et à bien positionner les & des lignes de continuation
102!                 (les placer en colonne 6 et en colonne 73)
103!-----------------------------------------------------------------------
104! INCLUDE comdissipn.h
105
106      REAL  tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
107!
108      COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,     &
109     &                        cdivu,      crot,         cdivh
110
111!
112!    Les parametres de ce common proviennent des calculs effectues dans
113!             Inidissip  .
114!
115!-----------------------------------------------------------------------
116!
117! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
118!
119!
120! NB: keep items of different kinds in seperate common blocs to avoid
121!     "misaligned commons" issues
122!-----------------------------------------------------------------------
123! INCLUDE 'logic.h'
124
125      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
126     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
127     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
128     &  ,ok_limit,ok_etat0,hybrid                                       &
129     &  ,moyzon_mu,moyzon_ch
130
131      COMMON/logici/ iflag_phys,iflag_trac
132     
133      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
134     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
135     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
136     &  ,ok_limit,ok_etat0
137      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
138                     ! (only used if disvert_type==2)
139      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
140
141      integer iflag_phys,iflag_trac
142!$OMP THREADPRIVATE(/logicl/)
143!$OMP THREADPRIVATE(/logici/)
144!-----------------------------------------------------------------------
145c
146      INTEGER klevel
147      REAL h( ip1jmp1,klevel ), divgra( ip1jmp1,klevel )
148c
149      REAL ghy(ip1jm,llm), ghx(ip1jmp1,llm)
150
151      INTEGER  l,ij,iter,lh
152c
153c
154c
155      CALL SCOPY ( ip1jmp1*klevel,h,1,divgra,1 )
156c
157      DO 10 iter = 1,lh
158
159      CALL filtreg ( divgra,jjp1,klevel,2,1,.true.,1  )
160
161      CALL    grad (klevel,divgra, ghx  , ghy          )
162      CALL  diverg (klevel,  ghx , ghy  , divgra       )
163
164      CALL filtreg ( divgra,jjp1,klevel,2,1,.true.,1)
165
166      DO 5 l = 1,klevel
167      DO 4  ij = 1, ip1jmp1
168      divgra( ij,l ) = - cdivh * divgra( ij,l )
169   4  CONTINUE
170   5  CONTINUE
171c
172  10  CONTINUE
173      RETURN
174      END
Note: See TracBrowser for help on using the repository browser.