source: LMDZ5/trunk/libf/dyn3d/fluxstokenc.F @ 2597

Last change on this file since 2597 was 2597, checked in by Ehouarn Millour, 8 years ago

Cleanup in the dynamics: get rid of comconst.h, make it a module comconst_mod.
EM

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