source: LMDZ4/branches/LMDZ4_par_0/libf/dyn3dpar/fluxstokenc_p.F @ 1379

Last change on this file since 1379 was 630, checked in by Laurent Fairhead, 19 years ago

Import d'une version parallele de la dynamique YM
LF

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.3 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 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 fluxid, fluxvid,fluxdid
42 
43      SAVE iadvtr, massem,pbaruc,pbarvc,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
52      if(first) then
53
54        CALL initfluxsto_p( 'fluxstoke',
55     .  time_step,istdyn* time_step,istdyn* time_step,
56     . nqmx, fluxid,fluxvid,fluxdid)
57       
58        ijb=ij_begin
59        ije=ij_end
60        jjn=jj_nb
61
62        ndex(1) = 0
63        call histwrite(fluxid, 'phis', 1, phis(ijb:ije),
64     .                 iip1*jjn, ndex)
65        call histwrite(fluxid, 'aire', 1, aire(ijb:ije),
66     .                 iip1*jjn, ndex)
67       
68        ndex(1) = 0
69        nscal = 1
70       
71        if (mpi_rank==0) then
72          tst(1) = time_step
73          call histwrite(fluxdid, 'dtvr', 1, tst, nscal, ndex)
74          ist(1)=istdyn
75          call histwrite(fluxdid, 'istdyn', 1, ist, nscal, ndex)
76          istp(1)= istphy
77          call histwrite(fluxdid, 'istphy', 1, istp, nscal, ndex)
78        endif
79        first = .false.
80
81      endif
82
83
84      IF(iadvtr.EQ.0) THEN
85cym         CALL initial0(ijp1llm,phic)
86cym        CALL initial0(ijp1llm,tetac)
87cym         CALL initial0(ijp1llm,pbaruc)
88cym         CALL initial0(ijmllm,pbarvc)
89        ijb=ij_begin
90        ije=ij_end
91        phic(ijb:ije,1:llm)=0
92        tetac(ijb:ije,1:llm)=0
93        pbaruc(ijb:ije,1:llm)=0
94       
95        if (pole_sud) ije=ij_end-iip1
96        pbarvc(ijb:ije,1:llm)=0
97      ENDIF
98
99c   accumulation des flux de masse horizontaux
100      ijb=ij_begin
101      ije=ij_end
102     
103      DO l=1,llm
104         DO ij = ijb,ije
105            pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)
106            tetac(ij,l) = tetac(ij,l) + teta(ij,l)
107            phic(ij,l) = phic(ij,l) + phi(ij,l)
108         ENDDO
109       ENDDO
110     
111      ijb=ij_begin
112      ije=ij_end
113      if (pole_sud) ije=ij_end-iip1
114       
115      DO l=1,llm
116         DO ij = ijb,ije
117            pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)
118         ENDDO
119      ENDDO
120
121c   selection de la masse instantannee des mailles avant le transport.
122      IF(iadvtr.EQ.0) THEN
123cym         CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)
124        ijb=ij_begin
125        ije=ij_end
126        massem(ijb:ije,1:llm)=masse(ijb:ije,1:llm)
127      ENDIF
128
129      iadvtr   = iadvtr+1
130
131
132c   Test pour savoir si on advecte a ce pas de temps
133      IF ( iadvtr.EQ.istdyn ) THEN
134c    normalisation
135      ijb=ij_begin
136      ije=ij_end
137
138      DO l=1,llm
139         DO ij = ijb,ije
140            pbaruc(ij,l) = pbaruc(ij,l)/float(istdyn)
141            tetac(ij,l) = tetac(ij,l)/float(istdyn)
142            phic(ij,l) = phic(ij,l)/float(istdyn)
143         ENDDO
144      ENDDO
145
146      ijb=ij_begin
147      ije=ij_end
148      if (pole_sud) ije=ij_end-iip1     
149     
150      DO l=1,llm
151          DO ij = ijb,ije
152            pbarvc(ij,l) = pbarvc(ij,l)/float(istdyn)
153         ENDDO
154      ENDDO
155
156c   traitement des flux de masse avant advection.
157c     1. calcul de w
158c     2. groupement des mailles pres du pole.
159
160        call Register_Hallo(pbaruc,ip1jmp1,llm,1,1,1,1,Req)
161        call Register_Hallo(pbarvc,ip1jm,llm,1,1,1,1,Req)
162        call SendRequest(Req)
163        call WaitRequest(Req)
164
165        CALL groupe_p( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )
166       
167        jjb=jj_begin
168        jje=jj_end
169        if (pole_sud) jje=jj_end-1
170       
171        do l=1,llm
172           do j=jjb,jje
173              do i=1,iip1
174                 pbarvst(i,j,l)=pbarvg(i,j,l)
175              enddo
176           enddo
177         enddo
178         
179         if (pole_sud) then
180           do i=1,iip1
181              pbarvst(i,jjp1,l)=0.
182           enddo
183        endif
184     
185         iadvtr=0
186        Print*,'ITAU auqel on stoke les fluxmasses',itau
187       
188        ijb=ij_begin
189        ije=ij_end
190        jjn=jj_nb
191       
192        call histwrite(fluxid, 'masse', itau, massem(ijb:ije,:),
193     .               iip1*jjn*llm, ndex)
194       
195        call histwrite(fluxid, 'pbaru', itau, pbarug(ijb:ije,:),
196     .               iip1*jjn*llm, ndex)
197       
198        jjb=jj_begin
199        jje=jj_end
200        jjn=jj_nb
201        if (pole_sud) then
202          jje=jj_end-1
203          jjn=jj_nb-1
204        endif
205       
206        call histwrite(fluxvid, 'pbarv', itau, pbarvg(:,jjb:jje,:),
207     .               iip1*jjn*llm, ndex)
208       
209        ijb=ij_begin
210        ije=ij_end
211        jjn=jj_nb
212       
213        call histwrite(fluxid, 'w' ,itau, wg(ijb:ije,:),
214     .             iip1*jjn*llm, ndex)
215       
216        call histwrite(fluxid, 'teta' ,itau, tetac(ijb:ije,:),
217     .             iip1*jjn*llm, ndex)
218       
219        call histwrite(fluxid, 'phi' ,itau, phic(ijb:ije,:),
220     .             iip1*jjn*llm, ndex)
221       
222C
223
224      ENDIF ! if iadvtr.EQ.istdyn
225
226      RETURN
227      END
Note: See TracBrowser for help on using the repository browser.