source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/config/ppsrc/dyn3d_common/nxgrarot.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 nxgrarot (klevel,xcov, ycov, lr, grx, gry )
5c   ***********************************************************
6c
7c    Auteur :  P.Le Van 
8c
9c                                 lr
10c      calcul de  ( nXgrad (rot) )   du vect. v  ....
11c
12c       xcov et ycov  etant les compos. covariantes de  v
13c   ***********************************************************
14c     xcov , ycov et lr  sont des arguments  d'entree pour le s-prog
15c      grx   et  gry     sont des arguments de sortie pour le s-prog
16c
17c
18      IMPLICIT NONE
19c
20c
21!-----------------------------------------------------------------------
22!   INCLUDE 'dimensions.h'
23!
24!   dimensions.h contient les dimensions du modele
25!   ndm est tel que iim=2**ndm
26!-----------------------------------------------------------------------
27
28      INTEGER iim,jjm,llm,ndm
29
30      PARAMETER (iim= 128,jjm=96,llm=64,ndm=1)
31
32!-----------------------------------------------------------------------
33!
34! $Header$
35!
36!
37!  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
38!                 veillez  n'utiliser que des ! pour les commentaires
39!                 et  bien positionner les & des lignes de continuation
40!                 (les placer en colonne 6 et en colonne 73)
41!
42!
43!-----------------------------------------------------------------------
44!   INCLUDE 'paramet.h'
45
46      INTEGER  iip1,iip2,iip3,jjp1,llmp1,llmp2,llmm1
47      INTEGER  kftd,ip1jm,ip1jmp1,ip1jmi1,ijp1llm
48      INTEGER  ijmllm,mvar
49      INTEGER jcfil,jcfllm
50
51      PARAMETER( iip1= iim+1,iip2=iim+2,iip3=iim+3                       &
52     &    ,jjp1=jjm+1-1/jjm)
53      PARAMETER( llmp1 = llm+1,  llmp2 = llm+2, llmm1 = llm-1 )
54      PARAMETER( kftd  = iim/2 -ndm )
55      PARAMETER( ip1jm  = iip1*jjm,  ip1jmp1= iip1*jjp1 )
56      PARAMETER( ip1jmi1= ip1jm - iip1 )
57      PARAMETER( ijp1llm= ip1jmp1 * llm, ijmllm= ip1jm * llm )
58      PARAMETER( mvar= ip1jmp1*( 2*llm+1) + ijmllm )
59      PARAMETER( jcfil=jjm/2+5, jcfllm=jcfil*llm )
60
61!-----------------------------------------------------------------------
62!
63! $Header$
64!
65!  Attention : ce fichier include est compatible format fixe/format libre
66!                 veillez à n'utiliser que des ! pour les commentaires
67!                 et à bien positionner les & des lignes de continuation
68!                 (les placer en colonne 6 et en colonne 73)
69!-----------------------------------------------------------------------
70! INCLUDE comdissipn.h
71
72      REAL  tetaudiv, tetaurot, tetah, cdivu, crot, cdivh
73!
74      COMMON/comdissipn/ tetaudiv(llm),tetaurot(llm),tetah(llm)   ,     &
75     &                        cdivu,      crot,         cdivh
76
77!
78!    Les parametres de ce common proviennent des calculs effectues dans
79!             Inidissip  .
80!
81!-----------------------------------------------------------------------
82!
83! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
84!
85!
86! NB: keep items of different kinds in seperate common blocs to avoid
87!     "misaligned commons" issues
88!-----------------------------------------------------------------------
89! INCLUDE 'logic.h'
90
91      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
92     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
93     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
94     &  ,ok_limit,ok_etat0,hybrid                                       &
95     &  ,moyzon_mu,moyzon_ch
96
97      COMMON/logici/ iflag_phys,iflag_trac
98     
99      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
100     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
101     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
102     &  ,ok_limit,ok_etat0
103      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
104                     ! (only used if disvert_type==2)
105      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
106
107      integer iflag_phys,iflag_trac
108!$OMP THREADPRIVATE(/logicl/)
109!$OMP THREADPRIVATE(/logici/)
110!-----------------------------------------------------------------------
111c
112      INTEGER klevel
113      REAL xcov( ip1jmp1,klevel ), ycov( ip1jm,klevel )
114      REAL  grx( ip1jmp1,klevel ),  gry( ip1jm,klevel )
115c
116      REAL rot(ip1jm,llm)
117
118      INTEGER l,ij,iter,lr
119c
120c
121c
122      CALL SCOPY ( ip1jmp1*klevel, xcov, 1, grx, 1 )
123      CALL SCOPY (  ip1jm*klevel, ycov, 1, gry, 1 )
124c
125      DO 10 iter = 1,lr
126      CALL  rotat (klevel,grx, gry, rot )
127      CALL filtreg( rot, jjm, klevel, 2,1, .false.,2)
128      CALL nxgrad (klevel,rot, grx, gry )
129c
130      DO 5  l = 1, klevel
131      DO 2 ij = 1, ip1jm
132      gry( ij,l ) = - gry( ij,l ) * crot
133   2  CONTINUE
134      DO 3 ij = 1, ip1jmp1
135      grx( ij,l ) = - grx( ij,l ) * crot
136   3  CONTINUE
137   5  CONTINUE
138c
139  10  CONTINUE
140      RETURN
141      END
Note: See TracBrowser for help on using the repository browser.