source: LMDZ4/tags/pre_parallel/libf/dyn3d/fluxstokenc.F @ 730

Last change on this file since 730 was 730, checked in by (none), 18 years ago

This commit was manufactured by cvs2svn to create tag 'pre_parallel'.

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 4.0 KB
Line 
1      SUBROUTINE fluxstokenc(pbaru,pbarv,masse,teta,phi,phis,
2     . time_step,itau )
3
4       USE IOIPSL
5c
6c     Auteur :  F. Hourdin
7c
8c
9ccc   ..   Modif. P. Le Van  ( 20/12/97 )  ...
10c
11      IMPLICIT NONE
12c
13#include "dimensions.h"
14#include "paramet.h"
15#include "comconst.h"
16#include "comvert.h"
17#include "comgeom.h"
18#include "tracstoke.h"
19#include "temps.h"
20
21      REAL time_step,t_wrt, t_ops
22      REAL pbaru(ip1jmp1,llm),pbarv(ip1jm,llm)
23      REAL masse(ip1jmp1,llm),teta(ip1jmp1,llm),phi(ip1jmp1,llm)
24      REAL phis(ip1jmp1)
25
26      REAL pbaruc(ip1jmp1,llm),pbarvc(ip1jm,llm)
27      REAL massem(ip1jmp1,llm),tetac(ip1jmp1,llm),phic(ip1jmp1,llm)
28
29      REAL pbarug(ip1jmp1,llm),pbarvg(iip1,jjm,llm),wg(ip1jmp1,llm)
30
31      REAL pbarvst(iip1,jjp1,llm),zistdyn
32        real dtcum
33
34      INTEGER iadvtr,ndex(1)
35      integer nscal
36      real tst(1),ist(1),istp(1)
37      INTEGER ij,l,irec,i,j,itau
38      INTEGER, SAVE :: fluxid, fluxvid,fluxdid
39 
40      SAVE iadvtr, massem,pbaruc,pbarvc,irec
41      SAVE phic,tetac
42      logical first
43      save first
44      data first/.true./
45      DATA iadvtr/0/
46
47
48c AC initialisations
49      pbarug(:,:)   = 0.
50      pbarvg(:,:,:) = 0.
51      wg(:,:)       = 0.
52     
53
54      if(first) then
55
56        CALL initfluxsto( 'fluxstoke',
57     .  time_step,istdyn* time_step,istdyn* time_step,
58     . nqmx, fluxid,fluxvid,fluxdid)
59       
60        ndex(1) = 0
61        call histwrite(fluxid, 'phis', 1, phis, iip1*jjp1, ndex)
62        call histwrite(fluxid, 'aire', 1, aire, iip1*jjp1, ndex)
63       
64        ndex(1) = 0
65        nscal = 1
66        tst(1) = time_step
67        call histwrite(fluxdid, 'dtvr', 1, tst, nscal, ndex)
68        ist(1)=istdyn
69        call histwrite(fluxdid, 'istdyn', 1, ist, nscal, ndex)
70        istp(1)= istphy
71        call histwrite(fluxdid, 'istphy', 1, istp, nscal, ndex)
72       
73        first = .false.
74
75      endif
76
77
78      IF(iadvtr.EQ.0) THEN
79         CALL initial0(ijp1llm,phic)
80         CALL initial0(ijp1llm,tetac)
81         CALL initial0(ijp1llm,pbaruc)
82         CALL initial0(ijmllm,pbarvc)
83      ENDIF
84
85c   accumulation des flux de masse horizontaux
86      DO l=1,llm
87         DO ij = 1,ip1jmp1
88            pbaruc(ij,l) = pbaruc(ij,l) + pbaru(ij,l)
89            tetac(ij,l) = tetac(ij,l) + teta(ij,l)
90            phic(ij,l) = phic(ij,l) + phi(ij,l)
91         ENDDO
92         DO ij = 1,ip1jm
93            pbarvc(ij,l) = pbarvc(ij,l) + pbarv(ij,l)
94         ENDDO
95      ENDDO
96
97c   selection de la masse instantannee des mailles avant le transport.
98      IF(iadvtr.EQ.0) THEN
99         CALL SCOPY(ip1jmp1*llm,masse,1,massem,1)
100      ENDIF
101
102      iadvtr   = iadvtr+1
103
104
105c   Test pour savoir si on advecte a ce pas de temps
106      IF ( iadvtr.EQ.istdyn ) THEN
107c    normalisation
108      DO l=1,llm
109         DO ij = 1,ip1jmp1
110            pbaruc(ij,l) = pbaruc(ij,l)/float(istdyn)
111            tetac(ij,l) = tetac(ij,l)/float(istdyn)
112            phic(ij,l) = phic(ij,l)/float(istdyn)
113         ENDDO
114         DO ij = 1,ip1jm
115            pbarvc(ij,l) = pbarvc(ij,l)/float(istdyn)
116         ENDDO
117      ENDDO
118
119c   traitement des flux de masse avant advection.
120c     1. calcul de w
121c     2. groupement des mailles pres du pole.
122
123        CALL groupe( massem, pbaruc,pbarvc, pbarug,pbarvg,wg )
124
125        do l=1,llm
126           do j=1,jjm
127              do i=1,iip1
128                 pbarvst(i,j,l)=pbarvg(i,j,l)
129              enddo
130           enddo
131           do i=1,iip1
132              pbarvst(i,jjp1,l)=0.
133           enddo
134        enddo
135
136         iadvtr=0
137        Print*,'ITAU auqel on stoke les fluxmasses',itau
138       
139        call histwrite(fluxid, 'masse', itau, massem,
140     .               iip1*jjp1*llm, ndex)
141       
142        call histwrite(fluxid, 'pbaru', itau, pbarug,
143     .               iip1*jjp1*llm, ndex)
144       
145        call histwrite(fluxvid, 'pbarv', itau, pbarvg,
146     .               iip1*jjm*llm, ndex)
147       
148        call histwrite(fluxid, 'w' ,itau, wg,
149     .             iip1*jjp1*llm, ndex)
150       
151        call histwrite(fluxid, 'teta' ,itau, tetac,
152     .             iip1*jjp1*llm, ndex)
153       
154        call histwrite(fluxid, 'phi' ,itau, phic,
155     .             iip1*jjp1*llm, ndex)
156       
157C
158
159      ENDIF ! if iadvtr.EQ.istdyn
160
161      RETURN
162      END
Note: See TracBrowser for help on using the repository browser.