source: LMDZ4/branches/LMDZ4-dev/libf/dyn3dpar/fluxstokenc_p.F @ 1085

Last change on this file since 1085 was 1021, checked in by lsce, 16 years ago

Portage sur ifort : variables déclarées en SAVE 2 fois
YM

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.5 KB
Line 
1      SUBROUTINE fluxstokenc_p(pbaru,pbarv,masse,teta,phi,phis,
2     . time_step,itau )
3
4       USE IOIPSL
5       USE parallel
6       USE misc_mod
7       USE mod_hallo
8c
9c     Auteur :  F. Hourdin
10c
11c
12ccc   ..   Modif. P. Le Van  ( 20/12/97 )  ...
13c
14      IMPLICIT NONE
15c
16#include "dimensions.h"
17#include "paramet.h"
18#include "comconst.h"
19#include "comvert.h"
20#include "comgeom.h"
21#include "tracstoke.h"
22#include "temps.h"
23
24      REAL time_step,t_wrt, t_ops
25      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
26      REAL masse(ip1jmp1,llm),teta(ip1jmp1,llm),phi(ip1jmp1,llm)
27      REAL phis(ip1jmp1)
28
29      REAL,SAVE :: pbaruc(ip1jmp1,llm),pbarvc(ip1jm,llm)
30      REAL massem(ip1jmp1,llm),tetac(ip1jmp1,llm),phic(ip1jmp1,llm)
31
32      REAL pbarug(ip1jmp1,llm),pbarvg(iip1,jjm,llm),wg(ip1jmp1,llm)
33
34      REAL pbarvst(iip1,jjp1,llm),zistdyn
35        real dtcum
36
37      INTEGER iadvtr,ndex(1)
38      integer nscal
39      real tst(1),ist(1),istp(1)
40      INTEGER ij,l,irec,i,j,itau
41      INTEGER,SAVE :: fluxid, fluxvid,fluxdid
42 
43      SAVE iadvtr, massem,irec
44      SAVE phic,tetac
45      logical first
46      save first
47      data first/.true./
48      DATA iadvtr/0/
49      integer :: ijb,ije,jjb,jje,jjn
50      type(Request) :: Req
51
52c AC initialisations
53cym      pbarug(:,:)   = 0.
54cym      pbarvg(:,:,:) = 0.
55cym      wg(:,:)       = 0.
56
57c$OMP MASTER
58
59      if(first) then
60
61        CALL initfluxsto_p( 'fluxstoke',
62     .  time_step,istdyn* time_step,istdyn* time_step,
63     . nqmx, fluxid,fluxvid,fluxdid)
64       
65        ijb=ij_begin
66        ije=ij_end
67        jjn=jj_nb
68
69        ndex(1) = 0
70        call histwrite(fluxid, 'phis', 1, phis(ijb:ije),
71     .                 iip1*jjn, ndex)
72        call histwrite(fluxid, 'aire', 1, aire(ijb:ije),
73     .                 iip1*jjn, ndex)
74       
75        ndex(1) = 0
76        nscal = 1
77       
78        if (mpi_rank==0) then
79          tst(1) = time_step
80          call histwrite(fluxdid, 'dtvr', 1, tst, nscal, ndex)
81          ist(1)=istdyn
82          call histwrite(fluxdid, 'istdyn', 1, ist, nscal, ndex)
83          istp(1)= istphy
84          call histwrite(fluxdid, 'istphy', 1, istp, nscal, ndex)
85        endif
86        first = .false.
87
88      endif
89
90
91      IF(iadvtr.EQ.0) THEN
92cym         CALL initial0(ijp1llm,phic)
93cym        CALL initial0(ijp1llm,tetac)
94cym         CALL initial0(ijp1llm,pbaruc)
95cym         CALL initial0(ijmllm,pbarvc)
96        ijb=ij_begin
97        ije=ij_end
98        phic(ijb:ije,1:llm)=0
99        tetac(ijb:ije,1:llm)=0
100        pbaruc(ijb:ije,1:llm)=0
101       
102        IF (pole_sud) ije=ij_end-iip1
103        pbarvc(ijb:ije,1:llm)=0
104      ENDIF
105
106c   accumulation des flux de masse horizontaux
107      ijb=ij_begin
108      ije=ij_end
109     
110      DO l=1,llm
111         DO ij = ijb,ije
112            pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)
113            tetac(ij,l) = tetac(ij,l) + teta(ij,l)
114            phic(ij,l) = phic(ij,l) + phi(ij,l)
115         ENDDO
116       ENDDO
117     
118      ijb=ij_begin
119      ije=ij_end
120      if (pole_sud) ije=ij_end-iip1
121       
122      DO l=1,llm
123         DO ij = ijb,ije
124            pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)
125         ENDDO
126      ENDDO
127
128c   selection de la masse instantannee des mailles avant le transport.
129      IF(iadvtr.EQ.0) THEN
130cym         CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)
131        ijb=ij_begin
132        ije=ij_end
133        massem(ijb:ije,1:llm)=masse(ijb:ije,1:llm)
134      ENDIF
135
136      iadvtr   = iadvtr+1
137
138c$OMP END MASTER
139c$OMP BARRIER
140c   Test pour savoir si on advecte a ce pas de temps
141      IF ( iadvtr.EQ.istdyn ) THEN
142c$OMP MASTER
143c    normalisation
144      ijb=ij_begin
145      ije=ij_end
146
147      DO l=1,llm
148         DO ij = ijb,ije
149            pbaruc(ij,l) = pbaruc(ij,l)/float(istdyn)
150            tetac(ij,l) = tetac(ij,l)/float(istdyn)
151            phic(ij,l) = phic(ij,l)/float(istdyn)
152         ENDDO
153      ENDDO
154
155      ijb=ij_begin
156      ije=ij_end
157      if (pole_sud) ije=ij_end-iip1     
158     
159      DO l=1,llm
160          DO ij = ijb,ije
161            pbarvc(ij,l) = pbarvc(ij,l)/float(istdyn)
162         ENDDO
163      ENDDO
164
165c   traitement des flux de masse avant advection.
166c     1. calcul de w
167c     2. groupement des mailles pres du pole.
168c$OMP END MASTER
169c$OMP BARRIER
170        call Register_Hallo(pbaruc,ip1jmp1,llm,1,1,1,1,Req)
171        call Register_Hallo(pbarvc,ip1jm,llm,1,1,1,1,Req)
172        call SendRequest(Req)
173c$OMP BARRIER
174        call WaitRequest(Req)
175c$OMP BARRIER
176c$OMP MASTER
177        CALL groupe_p( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )
178       
179        jjb=jj_begin
180        jje=jj_end
181        if (pole_sud) jje=jj_end-1
182       
183        do l=1,llm
184           do j=jjb,jje
185              do i=1,iip1
186                 pbarvst(i,j,l)=pbarvg(i,j,l)
187              enddo
188           enddo
189         enddo
190         
191         if (pole_sud) then
192           do i=1,iip1
193              pbarvst(i,jjp1,l)=0.
194           enddo
195        endif
196     
197         iadvtr=0
198        Print*,'ITAU auqel on stoke les fluxmasses',itau
199       
200        ijb=ij_begin
201        ije=ij_end
202        jjn=jj_nb
203       
204        call histwrite(fluxid, 'masse', itau, massem(ijb:ije,:),
205     .               iip1*jjn*llm, ndex)
206       
207        call histwrite(fluxid, 'pbaru', itau, pbarug(ijb:ije,:),
208     .               iip1*jjn*llm, ndex)
209       
210        jjb=jj_begin
211        jje=jj_end
212        jjn=jj_nb
213        if (pole_sud) then
214          jje=jj_end-1
215          jjn=jj_nb-1
216        endif
217       
218        call histwrite(fluxvid, 'pbarv', itau, pbarvg(:,jjb:jje,:),
219     .               iip1*jjn*llm, ndex)
220       
221        ijb=ij_begin
222        ije=ij_end
223        jjn=jj_nb
224       
225        call histwrite(fluxid, 'w' ,itau, wg(ijb:ije,:),
226     .             iip1*jjn*llm, ndex)
227       
228        call histwrite(fluxid, 'teta' ,itau, tetac(ijb:ije,:),
229     .             iip1*jjn*llm, ndex)
230       
231        call histwrite(fluxid, 'phi' ,itau, phic(ijb:ije,:),
232     .             iip1*jjn*llm, ndex)
233       
234C
235c$OMP END MASTER
236      ENDIF ! if iadvtr.EQ.istdyn
237
238      RETURN
239      END
Note: See TracBrowser for help on using the repository browser.