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

Last change on this file since 224 was 224, checked in by ymipsl, 10 years ago
File size: 4.8 KB
Line 
1      SUBROUTINE dteta1_p ( teta, pbaru, pbarv, dteta)
2      USE parallel_lmdz
3      USE write_field_p
4      IMPLICIT NONE
5
6c=======================================================================
7c
8c   Auteur:  P. Le Van
9c   -------
10c Modif F.Forget 03/94 (on retire q et dq  pour construire dteta1)
11c
12c   ********************************************************************
13c   ... calcul du terme de convergence horizontale du flux d'enthalpie
14c        potentielle   ......
15c   ********************************************************************
16c  .. teta,pbaru et pbarv sont des arguments d'entree  pour le s-pg ....
17c     dteta               sont des arguments de sortie pour le s-pg ....
18c
19c=======================================================================
20
21
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! $Id: logic.h 1520 2011-05-23 11:37:09Z emillour $
65!
66!
67! NB: keep items of different kinds in seperate common blocs to avoid
68!     "misaligned commons" issues
69!-----------------------------------------------------------------------
70! INCLUDE 'logic.h'
71
72      COMMON/logicl/ purmats,forward,leapf,apphys,                      &
73     &  statcl,conser,apdiss,apdelq,saison,ecripar,fxyhypb,ysinus       &
74     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
75     &  ,ok_limit,ok_etat0,hybrid                                       &
76     &  ,moyzon_mu,moyzon_ch
77
78      COMMON/logici/ iflag_phys,iflag_trac
79     
80      LOGICAL purmats,forward,leapf,apphys,statcl,conser,               &
81     & apdiss,apdelq,saison,ecripar,fxyhypb,ysinus                      &
82     &  ,read_start,ok_guide,ok_strato,tidal,ok_gradsfile               &
83     &  ,ok_limit,ok_etat0
84      logical hybrid ! vertical coordinate is hybrid if true (sigma otherwise)
85                     ! (only used if disvert_type==2)
86      logical moyzon_mu,moyzon_ch ! used for zonal averages in Titan
87
88      integer iflag_phys,iflag_trac
89!$OMP THREADPRIVATE(/logicl/)
90!$OMP THREADPRIVATE(/logici/)
91!-----------------------------------------------------------------------
92
93      REAL teta( ip1jmp1,llm ),pbaru( ip1jmp1,llm ),pbarv( ip1jm,llm)
94      REAL dteta( ip1jmp1,llm )
95      INTEGER   l,ij
96
97      REAL hbyv( ip1jm,llm ), hbxu( ip1jmp1,llm )
98
99c
100      INTEGER ijb,ije,jjb,jje
101
102     
103      jjb=jj_begin
104      jje=jj_end
105
106c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)   
107      DO 5 l = 1,llm
108     
109      ijb=ij_begin
110      ije=ij_end
111     
112      if (pole_nord) ijb=ij_begin+iip1
113      if (pole_sud)  ije=ij_end-iip1
114     
115      DO 1  ij = ijb, ije - 1
116        hbxu(ij,l) = pbaru(ij,l) * 0.5 * ( teta(ij,l)+teta(ij+1,l) )
117   1  CONTINUE
118
119c    .... correction pour  hbxu(iip1,j,l)  .....
120c    ....   hbxu(iip1,j,l)= hbxu(1,j,l) ....
121
122CDIR$ IVDEP
123      DO 2 ij = ijb+iip1-1, ije, iip1
124        hbxu( ij, l ) = hbxu( ij - iim, l )
125   2  CONTINUE
126
127      ijb=ij_begin-iip1
128      if (pole_nord) ijb=ij_begin
129     
130      DO 3 ij = ijb,ije
131        hbyv(ij,l)= pbarv(ij, l)* 0.5 * ( teta(ij, l)+teta(ij+iip1,l) )
132   3  CONTINUE
133
134       if (.not. pole_sud) then
135          hbxu(ije+1:ije+iip1,l) = 0
136          hbyv(ije+1:ije+iip1,l) = 0
137        endif
138       
139   5  CONTINUE
140c$OMP END DO NOWAIT
141       
142       
143        CALL  convflu_p ( hbxu, hbyv, llm, dteta )
144
145
146c    stockage dans  dh de la convergence horizont. filtree' du  flux
147c                  ....                           ...........
148c           d'enthalpie potentielle .
149     
150     
151      CALL filtreg_p( dteta,jjb,jje,jjp1, llm, 2, 2, .true., 1)
152     
153     
154      RETURN
155      END
Note: See TracBrowser for help on using the repository browser.